pantry-0.1.1.2: Content addressable Haskell package management

Safe HaskellNone
LanguageHaskell2010

Pantry

Contents

Description

Content addressable Haskell package management, providing for secure, reproducible acquisition of Haskell package contents and metadata.

Since: 0.1.0.0

Synopsis

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 HackageSecurityConfig Source #

Configuration for Hackage Security to securely download package metadata and contents from Hackage. 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.1.0.0

defaultHackageSecurityConfig :: HackageSecurityConfig Source #

Default HackageSecurityConfig value using the official Hackage server.

Since: 0.1.0.0

class HasPantryConfig env where Source #

An environment which contains a PantryConfig.

Since: 0.1.0.0

Methods

pantryConfigL :: Lens' env PantryConfig Source #

Lens to get or set the PantryConfig

Since: 0.1.0.0

Instances
HasPantryConfig PantryApp Source # 
Instance details

Defined in Pantry

withPantryConfig Source #

Arguments

:: HasLogFunc env 
=> Path Abs Dir

pantry root directory, where the SQLite database and Hackage downloads are kept.

-> HackageSecurityConfig

Hackage configuration. You probably want defaultHackageSecurityConfig.

-> HpackExecutable

When converting an hpack package.yaml file to a cabal file, what version of hpack should we use?

-> Int

Maximum connection count

-> (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

Convenience

data PantryApp Source #

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

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

Constructors

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) !BlobKey !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)

Different from DownloadInvalidSize since mismatchActual is a lower bound on the size from the server.

LocalInvalidSHA256 !(Path Abs File) !(Mismatch SHA256) 
LocalInvalidSize !(Path Abs File) !(Mismatch FileSize) 
UnknownArchiveType !ArchiveLocation 
InvalidTarFileType !ArchiveLocation !FilePath !FileType 
UnsupportedTarball !ArchiveLocation !Text 
NoHackageCryptographicHash !PackageIdentifier 
FailedToCloneRepo !Repo 
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 

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
Eq PackageName 
Instance details

Defined in Distribution.Types.PackageName

Data PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageName -> c PackageName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PackageName #

toConstr :: PackageName -> Constr #

dataTypeOf :: PackageName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PackageName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PackageName) #

gmapT :: (forall b. Data b => b -> b) -> PackageName -> PackageName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageName -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageName -> r #

gmapQ :: (forall d. Data d => d -> u) -> PackageName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageName -> m PackageName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageName -> m PackageName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageName -> m PackageName #

Ord PackageName 
Instance details

Defined in Distribution.Types.PackageName

Read PackageName 
Instance details

Defined in Distribution.Types.PackageName

Show PackageName 
Instance details

Defined in Distribution.Types.PackageName

IsString PackageName

mkPackageName

Since: Cabal-2.0.0.2

Instance details

Defined in Distribution.Types.PackageName

Generic PackageName 
Instance details

Defined in Distribution.Types.PackageName

Associated Types

type Rep PackageName :: Type -> Type #

Text PackageName 
Instance details

Defined in Distribution.Types.PackageName

Parsec PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

parsec :: CabalParsing m => m PackageName #

Pretty PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

pretty :: PackageName -> Doc #

NFData PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

rnf :: PackageName -> () #

Binary PackageName 
Instance details

Defined in Distribution.Types.PackageName

type Rep PackageName 
Instance details

Defined in Distribution.Types.PackageName

type Rep PackageName = D1 (MetaData "PackageName" "Distribution.Types.PackageName" "Cabal-2.4.0.1" True) (C1 (MetaCons "PackageName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ShortText)))

data Version #

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
Eq Version 
Instance details

Defined in Distribution.Types.Version

Methods

(==) :: Version -> Version -> Bool #

(/=) :: Version -> Version -> Bool #

Data Version 
Instance details

Defined in Distribution.Types.Version

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Version -> c Version #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Version #

toConstr :: Version -> Constr #

dataTypeOf :: Version -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Version) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version) #

gmapT :: (forall b. Data b => b -> b) -> Version -> Version #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r #

gmapQ :: (forall d. Data d => d -> u) -> Version -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Version -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Version -> m Version #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version #

Ord Version 
Instance details

Defined in Distribution.Types.Version

Read Version 
Instance details

Defined in Distribution.Types.Version

Show Version 
Instance details

Defined in Distribution.Types.Version

Generic Version 
Instance details

Defined in Distribution.Types.Version

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Text Version 
Instance details

Defined in Distribution.Types.Version

Methods

disp :: Version -> Doc #

parse :: ReadP r Version #

Parsec Version 
Instance details

Defined in Distribution.Types.Version

Methods

parsec :: CabalParsing m => m Version #

Pretty Version 
Instance details

Defined in Distribution.Types.Version

Methods

pretty :: Version -> Doc #

NFData Version 
Instance details

Defined in Distribution.Types.Version

Methods

rnf :: Version -> () #

Binary Version 
Instance details

Defined in Distribution.Types.Version

Methods

put :: Version -> Put #

get :: Get Version #

putList :: [Version] -> Put #

type Rep Version 
Instance details

Defined in Distribution.Types.Version

data FlagName #

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
Eq FlagName 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Data FlagName 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Methods

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 :: (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 #

Ord FlagName 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Read FlagName 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Show FlagName 
Instance details

Defined in Distribution.Types.GenericPackageDescription

IsString FlagName

mkFlagName

Since: Cabal-2.0.0.2

Instance details

Defined in Distribution.Types.GenericPackageDescription

Generic FlagName 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Associated Types

type Rep FlagName :: Type -> Type #

Methods

from :: FlagName -> Rep FlagName x #

to :: Rep FlagName x -> FlagName #

Text FlagName 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Methods

disp :: FlagName -> Doc #

parse :: ReadP r FlagName #

Parsec FlagName 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Methods

parsec :: CabalParsing m => m FlagName #

Pretty FlagName 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Methods

pretty :: FlagName -> Doc #

NFData FlagName 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Methods

rnf :: FlagName -> () #

Binary FlagName 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Methods

put :: FlagName -> Put #

get :: Get FlagName #

putList :: [FlagName] -> Put #

type Rep FlagName 
Instance details

Defined in Distribution.Types.GenericPackageDescription

type Rep FlagName = D1 (MetaData "FlagName" "Distribution.Types.GenericPackageDescription" "Cabal-2.4.0.1" True) (C1 (MetaCons "FlagName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ShortText)))

data PackageIdentifier #

The name and version of a package.

Constructors

PackageIdentifier 

Fields

Instances
Eq PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Data PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageIdentifier -> c PackageIdentifier #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PackageIdentifier #

toConstr :: PackageIdentifier -> Constr #

dataTypeOf :: PackageIdentifier -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PackageIdentifier) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PackageIdentifier) #

gmapT :: (forall b. Data b => b -> b) -> PackageIdentifier -> PackageIdentifier #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageIdentifier -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageIdentifier -> r #

gmapQ :: (forall d. Data d => d -> u) -> PackageIdentifier -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageIdentifier -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageIdentifier -> m PackageIdentifier #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageIdentifier -> m PackageIdentifier #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageIdentifier -> m PackageIdentifier #

Ord PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Read PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Show PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Generic PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Associated Types

type Rep PackageIdentifier :: Type -> Type #

Text PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Parsec PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Pretty PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

NFData PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Methods

rnf :: PackageIdentifier -> () #

Binary PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

type Rep PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

type Rep PackageIdentifier = D1 (MetaData "PackageIdentifier" "Distribution.Types.PackageId" "Cabal-2.4.0.1" False) (C1 (MetaCons "PackageIdentifier" PrefixI True) (S1 (MetaSel (Just "pkgName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PackageName) :*: S1 (MetaSel (Just "pkgVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version)))

Files

newtype FileSize Source #

File size in bytes

Since: 0.1.0.0

Constructors

FileSize Word 
Instances
Eq FileSize Source # 
Instance details

Defined in Pantry.Types

Ord FileSize Source # 
Instance details

Defined in Pantry.Types

Show FileSize Source # 
Instance details

Defined in Pantry.Types

Generic FileSize Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep FileSize :: Type -> Type #

Methods

from :: FileSize -> Rep FileSize x #

to :: Rep FileSize x -> FileSize #

NFData FileSize Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: FileSize -> () #

Hashable FileSize Source # 
Instance details

Defined in Pantry.Types

Methods

hashWithSalt :: Int -> FileSize -> Int #

hash :: FileSize -> Int #

ToJSON FileSize Source # 
Instance details

Defined in Pantry.Types

FromJSON FileSize Source # 
Instance details

Defined in Pantry.Types

PersistFieldSql FileSize Source # 
Instance details

Defined in Pantry.Types

PersistField FileSize Source # 
Instance details

Defined in Pantry.Types

Display FileSize Source # 
Instance details

Defined in Pantry.Types

type Rep FileSize Source # 
Instance details

Defined in Pantry.Types

type Rep FileSize = D1 (MetaData "FileSize" "Pantry.Types" "pantry-0.1.1.2-21cqbQSvwNA2RPFXyFmCZj" True) (C1 (MetaCons "FileSize" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word)))

newtype RelFilePath Source #

File path relative to the configuration file it was parsed from

Since: 0.1.0.0

Constructors

RelFilePath Text 
Instances
Eq RelFilePath Source # 
Instance details

Defined in Pantry.Types

Ord RelFilePath Source # 
Instance details

Defined in Pantry.Types

Show RelFilePath Source # 
Instance details

Defined in Pantry.Types

Generic RelFilePath Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RelFilePath :: Type -> Type #

NFData RelFilePath Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: RelFilePath -> () #

ToJSON RelFilePath Source # 
Instance details

Defined in Pantry.Types

FromJSON RelFilePath Source # 
Instance details

Defined in Pantry.Types

Display RelFilePath Source # 
Instance details

Defined in Pantry.Types

type Rep RelFilePath Source # 
Instance details

Defined in Pantry.Types

type Rep RelFilePath = D1 (MetaData "RelFilePath" "Pantry.Types" "pantry-0.1.1.2-21cqbQSvwNA2RPFXyFmCZj" True) (C1 (MetaCons "RelFilePath" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

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

Constructors

ResolvedPath 

Fields

Instances
Eq (ResolvedPath t) Source # 
Instance details

Defined in Pantry.Types

Ord (ResolvedPath t) Source # 
Instance details

Defined in Pantry.Types

Show (ResolvedPath t) Source # 
Instance details

Defined in Pantry.Types

Generic (ResolvedPath t) Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep (ResolvedPath t) :: Type -> Type #

Methods

from :: ResolvedPath t -> Rep (ResolvedPath t) x #

to :: Rep (ResolvedPath t) x -> ResolvedPath t #

NFData (ResolvedPath t) Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: ResolvedPath t -> () #

type Rep (ResolvedPath t) Source # 
Instance details

Defined in Pantry.Types

type Rep (ResolvedPath t) = D1 (MetaData "ResolvedPath" "Pantry.Types" "pantry-0.1.1.2-21cqbQSvwNA2RPFXyFmCZj" False) (C1 (MetaCons "ResolvedPath" PrefixI True) (S1 (MetaSel (Just "resolvedRelative") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 RelFilePath) :*: S1 (MetaSel (Just "resolvedAbsolute") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Path Abs t))))

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
Functor Unresolved Source # 
Instance details

Defined in Pantry.Types

Methods

fmap :: (a -> b) -> Unresolved a -> Unresolved b #

(<$) :: a -> Unresolved b -> Unresolved a #

Applicative Unresolved Source # 
Instance details

Defined in Pantry.Types

Methods

pure :: a -> Unresolved a #

(<*>) :: Unresolved (a -> b) -> Unresolved a -> Unresolved b #

liftA2 :: (a -> b -> c) -> Unresolved a -> Unresolved b -> Unresolved c #

(*>) :: Unresolved a -> Unresolved b -> Unresolved b #

(<*) :: Unresolved a -> Unresolved b -> Unresolved a #

FromJSON (WithJSONWarnings (Unresolved (NonEmpty RawPackageLocationImmutable))) Source # 
Instance details

Defined in Pantry.Types

FromJSON (WithJSONWarnings (Unresolved (NonEmpty RawPackageLocation))) Source # 
Instance details

Defined in Pantry.Types

FromJSON (WithJSONWarnings (Unresolved RawSnapshotLayer)) Source # 
Instance details

Defined in Pantry.Types

FromJSON (WithJSONWarnings (Unresolved SnapshotLocation)) Source # 
Instance details

Defined in Pantry.Types

FromJSON (WithJSONWarnings (Unresolved RawSnapshotLocation)) Source # 
Instance details

Defined in Pantry.Types

FromJSON (WithJSONWarnings (Unresolved PackageLocationImmutable)) Source # 
Instance details

Defined in Pantry.Types

Cryptography

data SHA256 Source #

A SHA256 hash, stored in a static size for more efficient memory representation.

Since: 0.1.0.0

Instances
Eq SHA256 Source # 
Instance details

Defined in Pantry.SHA256

Methods

(==) :: SHA256 -> SHA256 -> Bool #

(/=) :: SHA256 -> SHA256 -> Bool #

Data SHA256 Source # 
Instance details

Defined in Pantry.SHA256

Methods

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 :: (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 #

Ord SHA256 Source # 
Instance details

Defined in Pantry.SHA256

Show SHA256 Source # 
Instance details

Defined in Pantry.SHA256

Generic SHA256 Source # 
Instance details

Defined in Pantry.SHA256

Associated Types

type Rep SHA256 :: Type -> Type #

Methods

from :: SHA256 -> Rep SHA256 x #

to :: Rep SHA256 x -> SHA256 #

NFData SHA256 Source # 
Instance details

Defined in Pantry.SHA256

Methods

rnf :: SHA256 -> () #

Hashable SHA256 Source # 
Instance details

Defined in Pantry.SHA256

Methods

hashWithSalt :: Int -> SHA256 -> Int #

hash :: SHA256 -> Int #

ToJSON SHA256 Source # 
Instance details

Defined in Pantry.SHA256

FromJSON SHA256 Source # 
Instance details

Defined in Pantry.SHA256

PersistFieldSql SHA256 Source # 
Instance details

Defined in Pantry.SHA256

PersistField SHA256 Source # 
Instance details

Defined in Pantry.SHA256

Display SHA256 Source # 
Instance details

Defined in Pantry.SHA256

type Rep SHA256 Source # 
Instance details

Defined in Pantry.SHA256

type Rep SHA256 = D1 (MetaData "SHA256" "Pantry.SHA256" "pantry-0.1.1.2-21cqbQSvwNA2RPFXyFmCZj" True) (C1 (MetaCons "SHA256" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bytes32)))

newtype TreeKey Source #

The hash of the binary representation of a Tree.

Since: 0.1.0.0

Constructors

TreeKey BlobKey 
Instances
Eq TreeKey Source # 
Instance details

Defined in Pantry.Types

Methods

(==) :: TreeKey -> TreeKey -> Bool #

(/=) :: TreeKey -> TreeKey -> Bool #

Ord TreeKey Source # 
Instance details

Defined in Pantry.Types

Show TreeKey Source # 
Instance details

Defined in Pantry.Types

Generic TreeKey Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep TreeKey :: Type -> Type #

Methods

from :: TreeKey -> Rep TreeKey x #

to :: Rep TreeKey x -> TreeKey #

NFData TreeKey Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: TreeKey -> () #

ToJSON TreeKey Source # 
Instance details

Defined in Pantry.Types

FromJSON TreeKey Source # 
Instance details

Defined in Pantry.Types

Display TreeKey Source # 
Instance details

Defined in Pantry.Types

type Rep TreeKey Source # 
Instance details

Defined in Pantry.Types

type Rep TreeKey = D1 (MetaData "TreeKey" "Pantry.Types" "pantry-0.1.1.2-21cqbQSvwNA2RPFXyFmCZj" True) (C1 (MetaCons "TreeKey" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BlobKey)))

data BlobKey Source #

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

Constructors

BlobKey !SHA256 !FileSize 
Instances
Eq BlobKey Source # 
Instance details

Defined in Pantry.Types

Methods

(==) :: BlobKey -> BlobKey -> Bool #

(/=) :: BlobKey -> BlobKey -> Bool #

Ord BlobKey Source # 
Instance details

Defined in Pantry.Types

Show BlobKey Source # 
Instance details

Defined in Pantry.Types

Generic BlobKey Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep BlobKey :: Type -> Type #

Methods

from :: BlobKey -> Rep BlobKey x #

to :: Rep BlobKey x -> BlobKey #

NFData BlobKey Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: BlobKey -> () #

ToJSON BlobKey Source # 
Instance details

Defined in Pantry.Types

FromJSON BlobKey Source # 
Instance details

Defined in Pantry.Types

Display BlobKey Source # 
Instance details

Defined in Pantry.Types

type Rep BlobKey Source # 
Instance details

Defined in Pantry.Types

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

Constructors

RawPackageMetadata 

Fields

Instances
Eq RawPackageMetadata Source # 
Instance details

Defined in Pantry.Types

Ord RawPackageMetadata Source # 
Instance details

Defined in Pantry.Types

Show RawPackageMetadata Source # 
Instance details

Defined in Pantry.Types

Generic RawPackageMetadata Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RawPackageMetadata :: Type -> Type #

NFData RawPackageMetadata Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: RawPackageMetadata -> () #

Display RawPackageMetadata Source # 
Instance details

Defined in Pantry.Types

type Rep RawPackageMetadata Source # 
Instance details

Defined in Pantry.Types

data PackageMetadata Source #

Exact metadata specifying concrete package

Since: 0.1.0.0

Constructors

PackageMetadata 

Fields

Instances
Eq PackageMetadata Source # 
Instance details

Defined in Pantry.Types

Ord PackageMetadata Source # 
Instance details

Defined in Pantry.Types

Show PackageMetadata Source # 
Instance details

Defined in Pantry.Types

Generic PackageMetadata Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep PackageMetadata :: Type -> Type #

NFData PackageMetadata Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: PackageMetadata -> () #

Display PackageMetadata Source # 
Instance details

Defined in Pantry.Types

type Rep PackageMetadata Source # 
Instance details

Defined in Pantry.Types

type Rep PackageMetadata = D1 (MetaData "PackageMetadata" "Pantry.Types" "pantry-0.1.1.2-21cqbQSvwNA2RPFXyFmCZj" False) (C1 (MetaCons "PackageMetadata" PrefixI True) (S1 (MetaSel (Just "pmIdent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PackageIdentifier) :*: (S1 (MetaSel (Just "pmTreeKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TreeKey) :*: S1 (MetaSel (Just "pmCabal") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 BlobKey))))

data Package Source #

Parsed tree with more information on the Haskell package it contains.

Since: 0.1.0.0

Constructors

Package 

Fields

Instances
Eq Package Source # 
Instance details

Defined in Pantry.Types

Methods

(==) :: Package -> Package -> Bool #

(/=) :: Package -> Package -> Bool #

Show Package Source # 
Instance details

Defined in Pantry.Types

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

Constructors

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 Maybe on FileSize is for compatibility with input that doesn't include the file size.

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. CFIHash should be preferred wherever possible for reproducibility.

Since: 0.1.0.0

Instances
Eq CabalFileInfo Source # 
Instance details

Defined in Pantry.Types

Ord CabalFileInfo Source # 
Instance details

Defined in Pantry.Types

Show CabalFileInfo Source # 
Instance details

Defined in Pantry.Types

Generic CabalFileInfo Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep CabalFileInfo :: Type -> Type #

NFData CabalFileInfo Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: CabalFileInfo -> () #

Hashable CabalFileInfo Source # 
Instance details

Defined in Pantry.Types

Display CabalFileInfo Source # 
Instance details

Defined in Pantry.Types

type Rep CabalFileInfo Source # 
Instance details

Defined in Pantry.Types

newtype Revision Source #

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

Constructors

Revision Word 
Instances
Eq Revision Source # 
Instance details

Defined in Pantry.Types

Data Revision Source # 
Instance details

Defined in Pantry.Types

Methods

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 :: (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 #

Ord Revision Source # 
Instance details

Defined in Pantry.Types

Show Revision Source # 
Instance details

Defined in Pantry.Types

Generic Revision Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep Revision :: Type -> Type #

Methods

from :: Revision -> Rep Revision x #

to :: Rep Revision x -> Revision #

NFData Revision Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: Revision -> () #

Hashable Revision Source # 
Instance details

Defined in Pantry.Types

Methods

hashWithSalt :: Int -> Revision -> Int #

hash :: Revision -> Int #

PersistFieldSql Revision Source # 
Instance details

Defined in Pantry.Types

PersistField Revision Source # 
Instance details

Defined in Pantry.Types

Display Revision Source # 
Instance details

Defined in Pantry.Types

type Rep Revision Source # 
Instance details

Defined in Pantry.Types

type Rep Revision = D1 (MetaData "Revision" "Pantry.Types" "pantry-0.1.1.2-21cqbQSvwNA2RPFXyFmCZj" True) (C1 (MetaCons "Revision" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word)))

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
Eq PackageIdentifierRevision Source # 
Instance details

Defined in Pantry.Types

Ord PackageIdentifierRevision Source # 
Instance details

Defined in Pantry.Types

Show PackageIdentifierRevision Source # 
Instance details

Defined in Pantry.Types

Generic PackageIdentifierRevision Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep PackageIdentifierRevision :: Type -> Type #

NFData PackageIdentifierRevision Source # 
Instance details

Defined in Pantry.Types

ToJSON PackageIdentifierRevision Source # 
Instance details

Defined in Pantry.Types

FromJSON PackageIdentifierRevision Source # 
Instance details

Defined in Pantry.Types

Display PackageIdentifierRevision Source # 
Instance details

Defined in Pantry.Types

type Rep PackageIdentifierRevision Source # 
Instance details

Defined in Pantry.Types

data UsePreferredVersions Source #

Should we pay attention to Hackage's preferred versions?

Since: 0.1.0.0

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

Constructors

RawArchive 

Fields

Instances
Eq RawArchive Source # 
Instance details

Defined in Pantry.Types

Ord RawArchive Source # 
Instance details

Defined in Pantry.Types

Show RawArchive Source # 
Instance details

Defined in Pantry.Types

Generic RawArchive Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RawArchive :: Type -> Type #

NFData RawArchive Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: RawArchive -> () #

type Rep RawArchive Source # 
Instance details

Defined in Pantry.Types

data Archive Source #

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

Constructors

Archive 

Fields

Instances
Eq Archive Source # 
Instance details

Defined in Pantry.Types

Methods

(==) :: Archive -> Archive -> Bool #

(/=) :: Archive -> Archive -> Bool #

Ord Archive Source # 
Instance details

Defined in Pantry.Types

Show Archive Source # 
Instance details

Defined in Pantry.Types

Generic Archive Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep Archive :: Type -> Type #

Methods

from :: Archive -> Rep Archive x #

to :: Rep Archive x -> Archive #

NFData Archive Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: Archive -> () #

type Rep Archive Source # 
Instance details

Defined in Pantry.Types

data ArchiveLocation Source #

Location that an archive is stored at

Since: 0.1.0.0

Constructors

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
Eq ArchiveLocation Source # 
Instance details

Defined in Pantry.Types

Ord ArchiveLocation Source # 
Instance details

Defined in Pantry.Types

Show ArchiveLocation Source # 
Instance details

Defined in Pantry.Types

Generic ArchiveLocation Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep ArchiveLocation :: Type -> Type #

NFData ArchiveLocation Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: ArchiveLocation -> () #

Display ArchiveLocation Source # 
Instance details

Defined in Pantry.Types

type Rep ArchiveLocation Source # 
Instance details

Defined in Pantry.Types

Repos

data Repo Source #

Information on packages stored in a source control repository.

Since: 0.1.0.0

Constructors

Repo 

Fields

  • repoUrl :: !Text

    Location of the repo

    Since: 0.1.0.0

  • repoCommit :: !Text

    Commit to use from the repo. It's strongly recommended to use a hash instead of a tag or branch name.

    Since: 0.1.0.0

  • repoType :: !RepoType

    The type of the repo

    Since: 0.1.0.0

  • repoSubdir :: !Text

    Subdirectory within the archive to get the package from.

    Since: 0.1.0.0

Instances
Eq Repo Source # 
Instance details

Defined in Pantry.Types

Methods

(==) :: Repo -> Repo -> Bool #

(/=) :: Repo -> Repo -> Bool #

Ord Repo Source # 
Instance details

Defined in Pantry.Types

Methods

compare :: Repo -> Repo -> Ordering #

(<) :: Repo -> Repo -> Bool #

(<=) :: Repo -> Repo -> Bool #

(>) :: Repo -> Repo -> Bool #

(>=) :: Repo -> Repo -> Bool #

max :: Repo -> Repo -> Repo #

min :: Repo -> Repo -> Repo #

Show Repo Source # 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> Repo -> ShowS #

show :: Repo -> String #

showList :: [Repo] -> ShowS #

Generic Repo Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep Repo :: Type -> Type #

Methods

from :: Repo -> Rep Repo x #

to :: Rep Repo x -> Repo #

NFData Repo Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: Repo -> () #

Display Repo Source # 
Instance details

Defined in Pantry.Types

type Rep Repo Source # 
Instance details

Defined in Pantry.Types

data RepoType Source #

The type of a source control repository.

Since: 0.1.0.0

Constructors

RepoGit 
RepoHg 
Instances
Eq RepoType Source # 
Instance details

Defined in Pantry.Types

Ord RepoType Source # 
Instance details

Defined in Pantry.Types

Show RepoType Source # 
Instance details

Defined in Pantry.Types

Generic RepoType Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RepoType :: Type -> Type #

Methods

from :: RepoType -> Rep RepoType x #

to :: Rep RepoType x -> RepoType #

NFData RepoType Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: RepoType -> () #

PersistFieldSql RepoType Source # 
Instance details

Defined in Pantry.Types

PersistField RepoType Source # 
Instance details

Defined in Pantry.Types

type Rep RepoType Source # 
Instance details

Defined in Pantry.Types

type Rep RepoType = D1 (MetaData "RepoType" "Pantry.Types" "pantry-0.1.1.2-21cqbQSvwNA2RPFXyFmCZj" False) (C1 (MetaCons "RepoGit" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RepoHg" PrefixI False) (U1 :: Type -> Type))

withRepo :: forall env a. (HasLogFunc env, HasProcessContext env) => Repo -> 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

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
Eq RawPackageLocation Source # 
Instance details

Defined in Pantry.Types

Show RawPackageLocation Source # 
Instance details

Defined in Pantry.Types

Generic RawPackageLocation Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RawPackageLocation :: Type -> Type #

NFData RawPackageLocation Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: RawPackageLocation -> () #

ToJSON RawPackageLocation Source # 
Instance details

Defined in Pantry.Types

FromJSON (WithJSONWarnings (Unresolved (NonEmpty RawPackageLocation))) Source # 
Instance details

Defined in Pantry.Types

type Rep RawPackageLocation Source # 
Instance details

Defined in Pantry.Types

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

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

Instances
Eq RawPackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Ord RawPackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Show RawPackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Generic RawPackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RawPackageLocationImmutable :: Type -> Type #

NFData RawPackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

ToJSON RawPackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Display RawPackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

FromJSON (WithJSONWarnings (Unresolved (NonEmpty RawPackageLocationImmutable))) Source # 
Instance details

Defined in Pantry.Types

type Rep RawPackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

data PackageLocationImmutable Source #

Location for remote packages or archives assumed to be immutable.

Since: 0.1.0.0

Instances
Eq PackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Ord PackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Show PackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Generic PackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep PackageLocationImmutable :: Type -> Type #

NFData PackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

ToJSON PackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Display PackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

FromJSON (WithJSONWarnings (Unresolved PackageLocationImmutable)) Source # 
Instance details

Defined in Pantry.Types

type Rep PackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Snapshots

data RawSnapshotLocation Source #

Where to load a snapshot from in raw form (RSUrl could have a missing BlobKey)

Since: 0.1.0.0

Constructors

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 BlobKey is used for reproducibility.

Since: 0.1.0.0

RSLFilePath !(ResolvedPath File)

Snapshot at a local file path.

Since: 0.1.0.0

Instances
Eq RawSnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Ord RawSnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Show RawSnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Generic RawSnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RawSnapshotLocation :: Type -> Type #

NFData RawSnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: RawSnapshotLocation -> () #

ToJSON RawSnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Display RawSnapshotLocation Source # 
Instance details

Defined in Pantry.Types

FromJSON (WithJSONWarnings (Unresolved RawSnapshotLocation)) Source # 
Instance details

Defined in Pantry.Types

type Rep RawSnapshotLocation Source # 
Instance details

Defined in Pantry.Types

data SnapshotLocation Source #

Where to load a snapshot from.

Since: 0.1.0.0

Constructors

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 BlobKey is used for reproducibility.

Since: 0.1.0.0

SLFilePath !(ResolvedPath File)

Snapshot at a local file path.

Since: 0.1.0.0

Instances
Eq SnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Ord SnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Show SnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Generic SnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep SnapshotLocation :: Type -> Type #

NFData SnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: SnapshotLocation -> () #

ToJSON SnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Display SnapshotLocation Source # 
Instance details

Defined in Pantry.Types

FromJSON (WithJSONWarnings (Unresolved SnapshotLocation)) Source # 
Instance details

Defined in Pantry.Types

type Rep SnapshotLocation Source # 
Instance details

Defined in Pantry.Types

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

Constructors

RawSnapshot 

Fields

data Snapshot Source #

A flattened representation of all the layers in a snapshot.

Since: 0.1.0.0

Constructors

Snapshot 

Fields

data RawSnapshotPackage Source #

Settings for a package found in a snapshot.

Since: 0.1.0.0

Constructors

RawSnapshotPackage 

Fields

data SnapshotPackage Source #

Settings for a package found in a snapshot.

Since: 0.1.0.0

Constructors

SnapshotPackage 

Fields

data RawSnapshotLayer Source #

A single layer of a snapshot, i.e. a specific YAML configuration file.

Since: 0.1.0.0

Constructors

RawSnapshotLayer 

Fields

Instances
Eq RawSnapshotLayer Source # 
Instance details

Defined in Pantry.Types

Show RawSnapshotLayer Source # 
Instance details

Defined in Pantry.Types

Generic RawSnapshotLayer Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RawSnapshotLayer :: Type -> Type #

NFData RawSnapshotLayer Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: RawSnapshotLayer -> () #

ToJSON RawSnapshotLayer Source # 
Instance details

Defined in Pantry.Types

FromJSON (WithJSONWarnings (Unresolved RawSnapshotLayer)) Source # 
Instance details

Defined in Pantry.Types

type Rep RawSnapshotLayer Source # 
Instance details

Defined in Pantry.Types

data SnapshotLayer Source #

A single layer of a snapshot, i.e. a specific YAML configuration file.

Since: 0.1.0.0

Constructors

SnapshotLayer 

Fields

Instances
Eq SnapshotLayer Source # 
Instance details

Defined in Pantry.Types

Show SnapshotLayer Source # 
Instance details

Defined in Pantry.Types

Generic SnapshotLayer Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep SnapshotLayer :: Type -> Type #

ToJSON SnapshotLayer Source # 
Instance details

Defined in Pantry.Types

type Rep SnapshotLayer Source # 
Instance details

Defined in Pantry.Types

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

Constructors

WCGhc !Version 
WCGhcGit !Text !Text 
WCGhcjs !Version !Version

GHCJS version followed by GHC version

Instances
Eq WantedCompiler Source # 
Instance details

Defined in Pantry.Types

Ord WantedCompiler Source # 
Instance details

Defined in Pantry.Types

Show WantedCompiler Source # 
Instance details

Defined in Pantry.Types

Generic WantedCompiler Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep WantedCompiler :: Type -> Type #

NFData WantedCompiler Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: WantedCompiler -> () #

ToJSON WantedCompiler Source # 
Instance details

Defined in Pantry.Types

FromJSON WantedCompiler Source # 
Instance details

Defined in Pantry.Types

FromJSONKey WantedCompiler Source # 
Instance details

Defined in Pantry.Types

Display WantedCompiler Source # 
Instance details

Defined in Pantry.Types

type Rep WantedCompiler Source # 
Instance details

Defined in Pantry.Types

Loading values

resolvePaths Source #

Arguments

:: MonadIO m 
=> Maybe (Path Abs Dir)

directory to use for relative paths

-> Unresolved a 
-> m a 

Resolve all of the file paths in an Unresolved relative to the given directory.

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 #

Arguments

:: (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

Since: 0.1.0.0

loadAndCompleteSnapshotRaw Source #

Arguments

:: (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

Since: 0.1.0.0

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 #

Arguments

:: (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

Completion functions

completePackageLocation :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env PackageLocationImmutable Source #

Fill in optional fields in a PackageLocationImmutable for more reproducible builds.

Since: 0.1.0.0

completeSnapshotLayer :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawSnapshotLayer -> RIO env SnapshotLayer Source #

Fill in optional fields in a SnapshotLayer 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

Parsers

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 defaul 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

parseFlagName :: String -> Maybe FlagName Source #

Parse a flag name from a Value.

Since: 0.1.0.0

parseVersion :: String -> Maybe Version Source #

Parse a version from a Value.

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

Stackage snapshots

ltsSnapshotLocation Source #

Arguments

:: Int

major version

-> Int

minor version

-> RawSnapshotLocation 

Location of an LTS snapshot

Since: 0.1.0.0

nightlySnapshotLocation :: Day -> RawSnapshotLocation Source #

Location of a Stackage Nightly snapshot

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

flagNameString :: FlagName -> String Source #

Render a flag name as a Value.

Since: 0.1.0.0

versionString :: Version -> String Source #

Render a version 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

Constructors

CabalString 

Fields

Instances
Eq a => Eq (CabalString a) Source # 
Instance details

Defined in Pantry.Types

Ord a => Ord (CabalString a) Source # 
Instance details

Defined in Pantry.Types

Show a => Show (CabalString a) Source # 
Instance details

Defined in Pantry.Types

Text a => ToJSON (CabalString a) Source # 
Instance details

Defined in Pantry.Types

Text a => ToJSONKey (CabalString a) Source # 
Instance details

Defined in Pantry.Types

IsCabalString a => FromJSON (CabalString a) Source # 
Instance details

Defined in Pantry.Types

IsCabalString a => FromJSONKey (CabalString a) Source # 
Instance details

Defined in Pantry.Types

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

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 #

Arguments

:: (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 #

Arguments

:: (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

loadCabalFile :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => PackageLocation -> RIO env GenericPackageDescription Source #

Same as loadCabalFileImmutable, but takes a PackageLocation. Never prints warnings, see loadCabalFilePath for that.

Since: 0.1.0.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 PackageLocationImmutables 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.

Note that, for now, this will not allow support for hpack files in these package locations. Instead, all PackageLocationImmutables will require a .cabal file. This may be relaxed in the future.

Since: 0.1.0.0

loadCabalFilePath Source #

Arguments

:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) 
=> 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.1.0.0

findOrGenerateCabalFile Source #

Arguments

:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) 
=> Path Abs Dir

package directory

-> RIO env (PackageName, Path Abs File) 

Get the filename 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.1.0.0

data PrintWarnings Source #

Should we print warnings when loading a cabal file?

Since: 0.1.0.0

Hackage index

updateHackageIndex Source #

Arguments

:: (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

Constructors

YesRequireHackageIndex

If there is nothing in the Hackage index, then perform an update

NoRequireHackageIndex

Do not perform an update

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 #

Returns the versions of the package available on Hackage.

Since: 0.1.0.0

getLatestHackageVersion Source #

Returns the latest version of the given package available from Hackage.

Since: 0.1.0.0

getLatestHackageLocation Source #

Returns location of the latest version of the given package available from Hackage.

Since: 0.1.0.0

getLatestHackageRevision Source #

Arguments

:: (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 #

Arguments

:: 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

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