pantry-0.10.0: Content addressable Haskell package management
Safe HaskellSafe-Inferred
LanguageHaskell2010

Pantry.Types

Synopsis

Documentation

data PantryConfig Source #

Configuration value used by the entire pantry package. Create one using withPantryConfig or withPantryConfig'. See also PantryApp for a convenience approach to using pantry.

Since: 0.1.0.0

Constructors

PantryConfig 

Fields

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

Instances details
Show PackageIndexConfig Source # 
Instance details

Defined in Pantry.Types

FromJSON (WithJSONWarnings PackageIndexConfig) Source #

If the hackage-security key is absent from the JSON object, assigns default value defaultHackageSecurityConfig.

Since: 0.6.0

Instance details

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

Instances

Instances details
Show HackageSecurityConfig Source # 
Instance details

Defined in Pantry.Types

FromJSON (WithJSONWarnings HackageSecurityConfig) Source #

If the ignore-expiry key is absent from the JSON object, assigns default value True.

Since: 0.1.1.0

Instance details

Defined in Pantry.Types

defaultHackageSecurityConfig :: HackageSecurityConfig Source #

Default HackageSecurityConfig value using the official Hackage server. The value of the hscIgnoreExpiry field is True.

Since: 0.7.0

data Storage Source #

Represents a SQL database connection.

Constructors

Storage 

Fields

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

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

Instances details
FromJSON BlobKey Source # 
Instance details

Defined in Pantry.Types

ToJSON 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 #

Show BlobKey Source # 
Instance details

Defined in Pantry.Types

NFData BlobKey Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: BlobKey -> () #

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

Display BlobKey Source # 
Instance details

Defined in Pantry.Types

type Rep BlobKey Source # 
Instance details

Defined in Pantry.Types

type Rep BlobKey = D1 ('MetaData "BlobKey" "Pantry.Types" "pantry-0.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" '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)))

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-syntax-2.0.0.2

Instances

Instances details
Parsec PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

parsec :: CabalParsing m => m PackageName #

Pretty PackageName 
Instance details

Defined in Distribution.Types.PackageName

Structured 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 :: forall r r'. (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 #

IsString PackageName

mkPackageName

Since: Cabal-syntax-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 #

Read PackageName 
Instance details

Defined in Distribution.Types.PackageName

Show PackageName 
Instance details

Defined in Distribution.Types.PackageName

Binary PackageName 
Instance details

Defined in Distribution.Types.PackageName

NFData PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

rnf :: PackageName -> () #

Eq PackageName 
Instance details

Defined in Distribution.Types.PackageName

Ord 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-syntax-3.10.1.0" '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-syntax-2.0.0.2

Instances

Instances details
Parsec Version 
Instance details

Defined in Distribution.Types.Version

Methods

parsec :: CabalParsing m => m Version #

Pretty Version 
Instance details

Defined in Distribution.Types.Version

Structured Version 
Instance details

Defined in Distribution.Types.Version

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 :: forall r r'. (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 #

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 #

Read Version 
Instance details

Defined in Distribution.Types.Version

Show Version 
Instance details

Defined in Distribution.Types.Version

Binary Version 
Instance details

Defined in Distribution.Types.Version

Methods

put :: Version -> Put #

get :: Get Version #

putList :: [Version] -> Put #

NFData Version 
Instance details

Defined in Distribution.Types.Version

Methods

rnf :: Version -> () #

Eq Version 
Instance details

Defined in Distribution.Types.Version

Methods

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

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

Ord Version 
Instance details

Defined in Distribution.Types.Version

type Rep Version 
Instance details

Defined in Distribution.Types.Version

data PackageIdentifier #

The name and version of a package.

Constructors

PackageIdentifier 

Fields

Instances

Instances details
Parsec PackageIdentifier
>>> simpleParsec "foo-bar-0" :: Maybe PackageIdentifier
Just (PackageIdentifier {pkgName = PackageName "foo-bar", pkgVersion = mkVersion [0]})
>>> simpleParsec "foo-bar" :: Maybe PackageIdentifier
Just (PackageIdentifier {pkgName = PackageName "foo-bar", pkgVersion = mkVersion []})

Note: Stricter than Text instance

>>> simpleParsec "foo-bar-0-0" :: Maybe PackageIdentifier
Nothing
>>> simpleParsec "foo-bar.0" :: Maybe PackageIdentifier
Nothing
>>> simpleParsec "foo-bar.4-2" :: Maybe PackageIdentifier
Nothing
>>> simpleParsec "1.2.3" :: Maybe PackageIdentifier
Nothing
Instance details

Defined in Distribution.Types.PackageId

Pretty PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Structured 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 :: forall r r'. (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 #

Generic PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Associated Types

type Rep PackageIdentifier :: Type -> Type #

Read PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Show PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Binary PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

NFData PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Methods

rnf :: PackageIdentifier -> () #

Eq PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Ord 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-syntax-3.10.1.0" 'False) (C1 ('MetaCons "PackageIdentifier" 'PrefixI 'True) (S1 ('MetaSel ('Just "pkgName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageName) :*: S1 ('MetaSel ('Just "pkgVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)))

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

Instances details
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 :: 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 # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep Revision :: Type -> Type #

Methods

from :: Revision -> Rep Revision x #

to :: Rep Revision x -> Revision #

Show Revision Source # 
Instance details

Defined in Pantry.Types

NFData Revision Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: Revision -> () #

Eq Revision Source # 
Instance details

Defined in Pantry.Types

Ord Revision Source # 
Instance details

Defined in Pantry.Types

Hashable Revision Source # 
Instance details

Defined in Pantry.Types

Methods

hashWithSalt :: Int -> Revision -> Int #

hash :: Revision -> Int #

PersistField Revision Source # 
Instance details

Defined in Pantry.Types

PersistFieldSql 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.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" 'True) (C1 ('MetaCons "Revision" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))

data ModuleName #

A valid Haskell module name.

Instances

Instances details
Parsec ModuleName 
Instance details

Defined in Distribution.ModuleName

Methods

parsec :: CabalParsing m => m ModuleName #

Pretty ModuleName 
Instance details

Defined in Distribution.ModuleName

Structured ModuleName 
Instance details

Defined in Distribution.ModuleName

Data ModuleName 
Instance details

Defined in Distribution.ModuleName

Methods

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

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

toConstr :: ModuleName -> Constr #

dataTypeOf :: ModuleName -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString ModuleName

Construct a ModuleName from a valid module name String.

This is just a convenience function intended for valid module strings. It is an error if it is used with a string that is not a valid module name. If you are parsing user input then use simpleParse instead.

Instance details

Defined in Distribution.ModuleName

Generic ModuleName 
Instance details

Defined in Distribution.ModuleName

Associated Types

type Rep ModuleName :: Type -> Type #

Read ModuleName 
Instance details

Defined in Distribution.ModuleName

Show ModuleName 
Instance details

Defined in Distribution.ModuleName

Binary ModuleName 
Instance details

Defined in Distribution.ModuleName

NFData ModuleName 
Instance details

Defined in Distribution.ModuleName

Methods

rnf :: ModuleName -> () #

Eq ModuleName 
Instance details

Defined in Distribution.ModuleName

Ord ModuleName 
Instance details

Defined in Distribution.ModuleName

Pretty ModuleName 
Instance details

Defined in Text.PrettyPrint.Leijen.Extended

type Rep ModuleName 
Instance details

Defined in Distribution.ModuleName

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

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

Instances details
Generic CabalFileInfo Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep CabalFileInfo :: Type -> Type #

Show CabalFileInfo Source # 
Instance details

Defined in Pantry.Types

NFData CabalFileInfo Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: CabalFileInfo -> () #

Eq CabalFileInfo Source # 
Instance details

Defined in Pantry.Types

Ord CabalFileInfo Source # 
Instance details

Defined in Pantry.Types

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

type Rep CabalFileInfo = D1 ('MetaData "CabalFileInfo" "Pantry.Types" "pantry-0.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" 'False) (C1 ('MetaCons "CFILatest" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CFIHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SHA256) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe FileSize))) :+: C1 ('MetaCons "CFIRevision" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Revision))))

data PrintWarnings Source #

Should we print warnings when loading a cabal file?

Since: 0.1.0.0

newtype PackageNameP Source #

Constructors

PackageNameP 

Instances

Instances details
FromJSON PackageNameP Source # 
Instance details

Defined in Pantry.Types

FromJSONKey PackageNameP Source # 
Instance details

Defined in Pantry.Types

ToJSON PackageNameP Source # 
Instance details

Defined in Pantry.Types

ToJSONKey PackageNameP Source # 
Instance details

Defined in Pantry.Types

Read PackageNameP Source # 
Instance details

Defined in Pantry.Types

Show PackageNameP Source # 
Instance details

Defined in Pantry.Types

NFData PackageNameP Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: PackageNameP -> () #

Eq PackageNameP Source # 
Instance details

Defined in Pantry.Types

Ord PackageNameP Source # 
Instance details

Defined in Pantry.Types

PersistField PackageNameP Source # 
Instance details

Defined in Pantry.Types

PersistFieldSql PackageNameP Source # 
Instance details

Defined in Pantry.Types

Display PackageNameP Source # 
Instance details

Defined in Pantry.Types

newtype VersionP Source #

Constructors

VersionP 

Fields

Instances

Instances details
FromJSON VersionP Source # 
Instance details

Defined in Pantry.Types

ToJSON VersionP Source # 
Instance details

Defined in Pantry.Types

Read VersionP Source # 
Instance details

Defined in Pantry.Types

Show VersionP Source # 
Instance details

Defined in Pantry.Types

NFData VersionP Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: VersionP -> () #

Eq VersionP Source # 
Instance details

Defined in Pantry.Types

Ord VersionP Source # 
Instance details

Defined in Pantry.Types

PersistField VersionP Source # 
Instance details

Defined in Pantry.Types

PersistFieldSql VersionP Source # 
Instance details

Defined in Pantry.Types

Display VersionP Source # 
Instance details

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

Instances details
FromJSON PackageIdentifierRevision Source # 
Instance details

Defined in Pantry.Types

ToJSON PackageIdentifierRevision Source # 
Instance details

Defined in Pantry.Types

Generic PackageIdentifierRevision Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep PackageIdentifierRevision :: Type -> Type #

Show PackageIdentifierRevision Source # 
Instance details

Defined in Pantry.Types

NFData PackageIdentifierRevision Source # 
Instance details

Defined in Pantry.Types

Eq PackageIdentifierRevision Source # 
Instance details

Defined in Pantry.Types

Ord 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

type Rep PackageIdentifierRevision = D1 ('MetaData "PackageIdentifierRevision" "Pantry.Types" "pantry-0.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" 'False) (C1 ('MetaCons "PackageIdentifierRevision" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PackageName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Version) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CabalFileInfo))))

pirForHash :: PackageIdentifier -> BlobKey -> PackageIdentifierRevision Source #

Package identifier and revision with a specified cabal file hash

Since: 0.1.0.0

data FileType Source #

Constructors

FTNormal 
FTExecutable 

Instances

Instances details
Bounded FileType Source # 
Instance details

Defined in Pantry.Types

Enum FileType Source # 
Instance details

Defined in Pantry.Types

Show FileType Source # 
Instance details

Defined in Pantry.Types

Eq FileType Source # 
Instance details

Defined in Pantry.Types

Ord FileType Source # 
Instance details

Defined in Pantry.Types

PersistField FileType Source # 
Instance details

Defined in Pantry.Types

PersistFieldSql FileType Source # 
Instance details

Defined in Pantry.Types

data BuildFile Source #

Instances

Instances details
Show BuildFile Source # 
Instance details

Defined in Pantry.Types

Eq BuildFile Source # 
Instance details

Defined in Pantry.Types

newtype FileSize Source #

File size in bytes

Since: 0.1.0.0

Constructors

FileSize Word 

Instances

Instances details
FromJSON FileSize Source # 
Instance details

Defined in Pantry.Types

ToJSON 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 #

Show FileSize Source # 
Instance details

Defined in Pantry.Types

NFData FileSize Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: FileSize -> () #

Eq FileSize Source # 
Instance details

Defined in Pantry.Types

Ord FileSize Source # 
Instance details

Defined in Pantry.Types

Hashable FileSize Source # 
Instance details

Defined in Pantry.Types

Methods

hashWithSalt :: Int -> FileSize -> Int #

hash :: FileSize -> Int #

PersistField FileSize Source # 
Instance details

Defined in Pantry.Types

PersistFieldSql 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.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" 'True) (C1 ('MetaCons "FileSize" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))

data TreeEntry Source #

Constructors

TreeEntry 

Fields

Instances

Instances details
Show TreeEntry Source # 
Instance details

Defined in Pantry.Types

Eq TreeEntry Source # 
Instance details

Defined in Pantry.Types

Ord TreeEntry Source # 
Instance details

Defined in Pantry.Types

hpackSafeFilePath :: SafeFilePath Source #

SafeFilePath for `package.yaml` file.

newtype TreeKey Source #

The hash of the binary representation of a Tree.

Since: 0.1.0.0

Constructors

TreeKey BlobKey 

Instances

Instances details
FromJSON TreeKey Source # 
Instance details

Defined in Pantry.Types

ToJSON 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 #

Show TreeKey Source # 
Instance details

Defined in Pantry.Types

NFData TreeKey Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: TreeKey -> () #

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

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.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" 'True) (C1 ('MetaCons "TreeKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlobKey)))

newtype Tree Source #

Represents the contents of a tree, which is a mapping from relative file paths to TreeEntrys.

Since: 0.1.0.0

Instances

Instances details
Show Tree Source # 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> Tree -> ShowS #

show :: Tree -> String #

showList :: [Tree] -> ShowS #

Eq Tree Source # 
Instance details

Defined in Pantry.Types

Methods

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

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

Ord Tree Source # 
Instance details

Defined in Pantry.Types

Methods

compare :: Tree -> Tree -> Ordering #

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

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

(>) :: Tree -> Tree -> Bool #

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

max :: Tree -> Tree -> Tree #

min :: Tree -> Tree -> Tree #

data SHA256 Source #

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

Since: 0.1.0.0

Instances

Instances details
FromJSON SHA256 Source # 
Instance details

Defined in Pantry.SHA256

ToJSON SHA256 Source # 
Instance details

Defined in Pantry.SHA256

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 :: 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 # 
Instance details

Defined in Pantry.SHA256

Associated Types

type Rep SHA256 :: Type -> Type #

Methods

from :: SHA256 -> Rep SHA256 x #

to :: Rep SHA256 x -> SHA256 #

Show SHA256 Source # 
Instance details

Defined in Pantry.SHA256

NFData SHA256 Source # 
Instance details

Defined in Pantry.SHA256

Methods

rnf :: SHA256 -> () #

Eq SHA256 Source # 
Instance details

Defined in Pantry.SHA256

Methods

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

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

Ord SHA256 Source # 
Instance details

Defined in Pantry.SHA256

Hashable SHA256 Source # 
Instance details

Defined in Pantry.SHA256

Methods

hashWithSalt :: Int -> SHA256 -> Int #

hash :: SHA256 -> Int #

PersistField SHA256 Source # 
Instance details

Defined in Pantry.SHA256

PersistFieldSql 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.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" 'True) (C1 ('MetaCons "SHA256" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bytes32)))

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

Instances details
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 #

Functor Unresolved Source # 
Instance details

Defined in Pantry.Types

Methods

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

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

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

Defined in Pantry.Types

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

Defined in Pantry.Types

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

Defined in Pantry.Types

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

Defined in Pantry.Types

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

Defined in Pantry.Types

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

Defined in Pantry.Types

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

Defined in Pantry.Types

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

data Package Source #

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

Since: 0.1.0.0

Constructors

Package 

Fields

Instances

Instances details
Show Package Source # 
Instance details

Defined in Pantry.Types

Eq Package Source # 
Instance details

Defined in Pantry.Types

Methods

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

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

Ord Package Source # 
Instance details

Defined in Pantry.Types

data PHpack Source #

Constructors

PHpack 

Fields

Instances

Instances details
Show PHpack Source # 
Instance details

Defined in Pantry.Types

Eq PHpack Source # 
Instance details

Defined in Pantry.Types

Methods

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

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

Ord PHpack Source # 
Instance details

Defined in Pantry.Types

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

Instances details
ToJSON RawPackageLocation Source # 
Instance details

Defined in Pantry.Types

Generic RawPackageLocation Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RawPackageLocation :: Type -> Type #

Show RawPackageLocation Source # 
Instance details

Defined in Pantry.Types

NFData RawPackageLocation Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: RawPackageLocation -> () #

Eq 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

type Rep RawPackageLocation = D1 ('MetaData "RawPackageLocation" "Pantry.Types" "pantry-0.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" 'False) (C1 ('MetaCons "RPLImmutable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RawPackageLocationImmutable)) :+: C1 ('MetaCons "RPLMutable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ResolvedPath Dir))))

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

Instances details
Generic PackageLocation Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep PackageLocation :: Type -> Type #

Show PackageLocation Source # 
Instance details

Defined in Pantry.Types

NFData PackageLocation Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: PackageLocation -> () #

Eq PackageLocation Source # 
Instance details

Defined in Pantry.Types

Display PackageLocation Source # 
Instance details

Defined in Pantry.Types

type Rep PackageLocation Source # 
Instance details

Defined in Pantry.Types

type Rep PackageLocation = D1 ('MetaData "PackageLocation" "Pantry.Types" "pantry-0.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" 'False) (C1 ('MetaCons "PLImmutable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PackageLocationImmutable)) :+: C1 ('MetaCons "PLMutable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ResolvedPath Dir))))

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

Instances details
ToJSON RawPackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Generic RawPackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RawPackageLocationImmutable :: Type -> Type #

Show RawPackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

NFData RawPackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Eq RawPackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Ord RawPackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Display RawPackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Pretty 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

Instances details
ToJSON PackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Generic PackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep PackageLocationImmutable :: Type -> Type #

Show PackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

NFData PackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Eq PackageLocationImmutable Source # 
Instance details

Defined in Pantry.Types

Ord 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

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

Instances details
Generic RawArchive Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RawArchive :: Type -> Type #

Show RawArchive Source # 
Instance details

Defined in Pantry.Types

NFData RawArchive Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: RawArchive -> () #

Eq RawArchive Source # 
Instance details

Defined in Pantry.Types

Ord RawArchive Source # 
Instance details

Defined in Pantry.Types

type Rep RawArchive Source # 
Instance details

Defined in Pantry.Types

type Rep RawArchive = D1 ('MetaData "RawArchive" "Pantry.Types" "pantry-0.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" 'False) (C1 ('MetaCons "RawArchive" 'PrefixI 'True) ((S1 ('MetaSel ('Just "raLocation") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ArchiveLocation) :*: S1 ('MetaSel ('Just "raHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe SHA256))) :*: (S1 ('MetaSel ('Just "raSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe FileSize)) :*: S1 ('MetaSel ('Just "raSubdir") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))))

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

Instances details
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 #

Show Archive Source # 
Instance details

Defined in Pantry.Types

NFData Archive Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: Archive -> () #

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

type Rep Archive Source # 
Instance details

Defined in Pantry.Types

type Rep Archive = D1 ('MetaData "Archive" "Pantry.Types" "pantry-0.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" '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))))

toRawArchive :: Archive -> RawArchive Source #

Convert archive to its "raw" equivalent.

Since: 0.1.0.0

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

Instances details
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 #

Show Repo Source # 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> Repo -> ShowS #

show :: Repo -> String #

showList :: [Repo] -> ShowS #

NFData Repo Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: Repo -> () #

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 #

Display Repo Source # 
Instance details

Defined in Pantry.Types

type Rep Repo Source # 
Instance details

Defined in Pantry.Types

type Rep Repo = D1 ('MetaData "Repo" "Pantry.Types" "pantry-0.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" '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))))

data AggregateRepo Source #

Instances

Instances details
Generic AggregateRepo Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep AggregateRepo :: Type -> Type #

Show AggregateRepo Source # 
Instance details

Defined in Pantry.Types

Eq AggregateRepo Source # 
Instance details

Defined in Pantry.Types

Ord AggregateRepo Source # 
Instance details

Defined in Pantry.Types

type Rep AggregateRepo Source # 
Instance details

Defined in Pantry.Types

type Rep AggregateRepo = D1 ('MetaData "AggregateRepo" "Pantry.Types" "pantry-0.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" 'False) (C1 ('MetaCons "AggregateRepo" 'PrefixI 'True) (S1 ('MetaSel ('Just "aRepo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SimpleRepo) :*: S1 ('MetaSel ('Just "aRepoSubdirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Text, RawPackageMetadata)])))

data SimpleRepo Source #

Repository without subdirectory information.

Since: 0.5.3

Constructors

SimpleRepo 

Instances

Instances details
Generic SimpleRepo Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep SimpleRepo :: Type -> Type #

Show SimpleRepo Source # 
Instance details

Defined in Pantry.Types

Eq SimpleRepo Source # 
Instance details

Defined in Pantry.Types

Ord SimpleRepo Source # 
Instance details

Defined in Pantry.Types

Display SimpleRepo Source # 
Instance details

Defined in Pantry.Types

type Rep SimpleRepo Source # 
Instance details

Defined in Pantry.Types

type Rep SimpleRepo = D1 ('MetaData "SimpleRepo" "Pantry.Types" "pantry-0.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" 'False) (C1 ('MetaCons "SimpleRepo" 'PrefixI 'True) (S1 ('MetaSel ('Just "sRepoUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "sRepoCommit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "sRepoType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RepoType))))

toAggregateRepos :: [(Repo, RawPackageMetadata)] -> [AggregateRepo] Source #

Group input repositories by non-subdir values.

data RepoType Source #

The type of a source control repository.

Since: 0.1.0.0

Constructors

RepoGit 
RepoHg 

Instances

Instances details
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 #

Show RepoType Source # 
Instance details

Defined in Pantry.Types

NFData RepoType Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: RepoType -> () #

Eq RepoType Source # 
Instance details

Defined in Pantry.Types

Ord RepoType Source # 
Instance details

Defined in Pantry.Types

PersistField RepoType Source # 
Instance details

Defined in Pantry.Types

PersistFieldSql 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.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" 'False) (C1 ('MetaCons "RepoGit" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RepoHg" 'PrefixI 'False) (U1 :: Type -> Type))

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

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

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

data OptionalSubdirs Source #

Constructors

OSSubdirs !(NonEmpty Text) 
OSPackageMetadata !Text !RawPackageMetadata

subdirectory and package metadata

Instances

Instances details
Generic OptionalSubdirs Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep OptionalSubdirs :: Type -> Type #

Show OptionalSubdirs Source # 
Instance details

Defined in Pantry.Types

NFData OptionalSubdirs Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: OptionalSubdirs -> () #

Eq OptionalSubdirs Source # 
Instance details

Defined in Pantry.Types

type Rep OptionalSubdirs 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

Instances details
Generic ArchiveLocation Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep ArchiveLocation :: Type -> Type #

Show ArchiveLocation Source # 
Instance details

Defined in Pantry.Types

NFData ArchiveLocation Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: ArchiveLocation -> () #

Eq ArchiveLocation Source # 
Instance details

Defined in Pantry.Types

Ord ArchiveLocation Source # 
Instance details

Defined in Pantry.Types

Display ArchiveLocation Source # 
Instance details

Defined in Pantry.Types

Pretty ArchiveLocation Source # 
Instance details

Defined in Pantry.Types

type Rep ArchiveLocation Source # 
Instance details

Defined in Pantry.Types

type Rep ArchiveLocation = D1 ('MetaData "ArchiveLocation" "Pantry.Types" "pantry-0.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" 'False) (C1 ('MetaCons "ALUrl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "ALFilePath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ResolvedPath File))))

newtype RelFilePath Source #

File path relative to the configuration file it was parsed from

Since: 0.1.0.0

Constructors

RelFilePath Text 

Instances

Instances details
FromJSON RelFilePath Source # 
Instance details

Defined in Pantry.Types

ToJSON RelFilePath Source # 
Instance details

Defined in Pantry.Types

Generic RelFilePath Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RelFilePath :: Type -> Type #

Show RelFilePath Source # 
Instance details

Defined in Pantry.Types

NFData RelFilePath Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: RelFilePath -> () #

Eq RelFilePath Source # 
Instance details

Defined in Pantry.Types

Ord 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.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" 'True) (C1 ('MetaCons "RelFilePath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype CabalString a Source #

Newtype wrapper for easier JSON integration with Cabal types.

Since: 0.1.0.0

Constructors

CabalString 

Fields

Instances

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

Defined in Pantry.Types

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

Defined in Pantry.Types

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

Defined in Pantry.Types

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

Defined in Pantry.Types

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

Defined in Pantry.Types

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

Defined in Pantry.Types

Ord a => Ord (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

data Mismatch a Source #

Constructors

Mismatch 

Fields

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 
NoLocalPackageDirFound !(Path Abs Dir) 
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 
InvalidGlobalHintsLocation !(Path Abs Dir) !Text 
InvalidFilePathGlobalHints !Text 
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)

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

LocalNoArchiveFileFound !(Path Abs File) 
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 
NoCasaConfig 
InvalidTreeFromCasa !BlobKey !ByteString 
ParseSnapNameException !Text 
HpackLibraryException !(Path Abs File) !String 
HpackExeException !FilePath !(Path Abs Dir) !SomeException 

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

Instances details
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 #

Show (ResolvedPath t) Source # 
Instance details

Defined in Pantry.Types

NFData (ResolvedPath t) Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: ResolvedPath t -> () #

Eq (ResolvedPath t) Source # 
Instance details

Defined in Pantry.Types

Ord (ResolvedPath t) Source # 
Instance details

Defined in Pantry.Types

type Rep (ResolvedPath t) Source # 
Instance details

Defined in Pantry.Types

type Rep (ResolvedPath t) = D1 ('MetaData "ResolvedPath" "Pantry.Types" "pantry-0.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" '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 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

Instances details
FromJSON WantedCompiler Source # 
Instance details

Defined in Pantry.Types

FromJSONKey WantedCompiler Source # 
Instance details

Defined in Pantry.Types

ToJSON WantedCompiler Source # 
Instance details

Defined in Pantry.Types

Generic WantedCompiler Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep WantedCompiler :: Type -> Type #

Show WantedCompiler Source # 
Instance details

Defined in Pantry.Types

NFData WantedCompiler Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: WantedCompiler -> () #

Eq WantedCompiler Source # 
Instance details

Defined in Pantry.Types

Ord 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

snapshotLocation :: HasPantryConfig env => SnapName -> RIO env RawSnapshotLocation Source #

Get the location of a snapshot synonym from the PantryConfig.

Since: 0.5.0.0

defaultSnapshotLocation :: SnapName -> RawSnapshotLocation Source #

Default location of snapshot synonyms, i.e. commercialhaskell's GitHub repository.

Since: 0.5.0.0

globalHintsLocation :: HasPantryConfig env => WantedCompiler -> RIO env GlobalHintsLocation Source #

Get the location of global hints from the PantryConfig.

Since: 0.9.4

defaultGlobalHintsLocation :: WantedCompiler -> GlobalHintsLocation Source #

Default location of global hints, i.e. commercialhaskell's GitHub repository.

Since: 0.9.4

data SnapName Source #

A snapshot synonym. It is expanded according to the field snapshotLocation of a PantryConfig.

@ since 0.5.0.0

Constructors

LTS 

Fields

  • !Int

    Major version

  • !Int

    Minor version ^ LTS Haskell snapshot, displayed as "lts-maj.min".

    Since: 0.5.0.0

Nightly !Day

Stackage Nightly snapshot, displayed as "nighly-YYYY-MM-DD".

Since: 0.5.0.0

Instances

Instances details
ToJSON SnapName Source # 
Instance details

Defined in Pantry.Types

Generic SnapName Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep SnapName :: Type -> Type #

Methods

from :: SnapName -> Rep SnapName x #

to :: Rep SnapName x -> SnapName #

Show SnapName Source # 
Instance details

Defined in Pantry.Types

NFData SnapName Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: SnapName -> () #

Eq SnapName Source # 
Instance details

Defined in Pantry.Types

Ord SnapName Source # 
Instance details

Defined in Pantry.Types

Display SnapName Source # 
Instance details

Defined in Pantry.Types

type Rep SnapName Source # 
Instance details

Defined in Pantry.Types

parseSnapName :: MonadThrow m => Text -> m SnapName Source #

Parse the short representation of a SnapName.

Since: 0.5.0.0

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

RSLSynonym !SnapName

Snapshot synonym (LTS/Nightly).

Since: 0.5.0.0

Instances

Instances details
ToJSON RawSnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Generic RawSnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RawSnapshotLocation :: Type -> Type #

Show RawSnapshotLocation Source # 
Instance details

Defined in Pantry.Types

NFData RawSnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: RawSnapshotLocation -> () #

Eq RawSnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Ord RawSnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Display RawSnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Pretty 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

Instances details
ToJSON SnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Generic SnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep SnapshotLocation :: Type -> Type #

Show SnapshotLocation Source # 
Instance details

Defined in Pantry.Types

NFData SnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: SnapshotLocation -> () #

Eq SnapshotLocation Source # 
Instance details

Defined in Pantry.Types

Ord 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

parseHackageText :: Text -> Either PantryException (PackageIdentifier, BlobKey) Source #

Parse a hackage text.

Since: 0.1.0.0

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

Instances details
ToJSON RawSnapshotLayer Source # 
Instance details

Defined in Pantry.Types

Generic RawSnapshotLayer Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RawSnapshotLayer :: Type -> Type #

Show RawSnapshotLayer Source # 
Instance details

Defined in Pantry.Types

NFData RawSnapshotLayer Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: RawSnapshotLayer -> () #

Eq 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

Instances details
ToJSON SnapshotLayer Source # 
Instance details

Defined in Pantry.Types

Generic SnapshotLayer Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep SnapshotLayer :: Type -> Type #

Show SnapshotLayer Source # 
Instance details

Defined in Pantry.Types

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

Instances

Instances details
Show SnapshotPackage Source # 
Instance details

Defined in Pantry.Types

data GlobalHintsLocation Source #

Where to load global hints from.

Since: 0.9.4

Constructors

GHLUrl !Text

Download the global hints from the given URL.

GHLFilePath !(ResolvedPath File)

Global hints at a local file path.

Instances

Instances details
ToJSON GlobalHintsLocation Source # 
Instance details

Defined in Pantry.Types

Generic GlobalHintsLocation Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep GlobalHintsLocation :: Type -> Type #

Show GlobalHintsLocation Source # 
Instance details

Defined in Pantry.Types

NFData GlobalHintsLocation Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: GlobalHintsLocation -> () #

Eq GlobalHintsLocation Source # 
Instance details

Defined in Pantry.Types

Ord GlobalHintsLocation Source # 
Instance details

Defined in Pantry.Types

Display GlobalHintsLocation Source # 
Instance details

Defined in Pantry.Types

Pretty GlobalHintsLocation Source # 
Instance details

Defined in Pantry.Types

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

Defined in Pantry.Types

type Rep GlobalHintsLocation Source # 
Instance details

Defined in Pantry.Types

type Rep GlobalHintsLocation = D1 ('MetaData "GlobalHintsLocation" "Pantry.Types" "pantry-0.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" 'False) (C1 ('MetaCons "GHLUrl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "GHLFilePath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ResolvedPath File))))

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

Instances details
Generic RawPackageMetadata Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RawPackageMetadata :: Type -> Type #

Show RawPackageMetadata Source # 
Instance details

Defined in Pantry.Types

NFData RawPackageMetadata Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: RawPackageMetadata -> () #

Eq RawPackageMetadata Source # 
Instance details

Defined in Pantry.Types

Ord RawPackageMetadata Source # 
Instance details

Defined in Pantry.Types

Display RawPackageMetadata Source # 
Instance details

Defined in Pantry.Types

type Rep RawPackageMetadata Source # 
Instance details

Defined in Pantry.Types

type Rep RawPackageMetadata = D1 ('MetaData "RawPackageMetadata" "Pantry.Types" "pantry-0.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" 'False) (C1 ('MetaCons "RawPackageMetadata" 'PrefixI 'True) (S1 ('MetaSel ('Just "rpmName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe PackageName)) :*: (S1 ('MetaSel ('Just "rpmVersion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Version)) :*: S1 ('MetaSel ('Just "rpmTreeKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe TreeKey)))))

data PackageMetadata Source #

Exact metadata specifying concrete package

Since: 0.1.0.0

Constructors

PackageMetadata 

Fields

Instances

Instances details
Generic PackageMetadata Source # 
Instance details

Defined in Pantry.Types

Associated Types

type Rep PackageMetadata :: Type -> Type #

Show PackageMetadata Source # 
Instance details

Defined in Pantry.Types

NFData PackageMetadata Source # 
Instance details

Defined in Pantry.Types

Methods

rnf :: PackageMetadata -> () #

Eq PackageMetadata Source # 
Instance details

Defined in Pantry.Types

Ord PackageMetadata Source # 
Instance details

Defined in Pantry.Types

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.10.0-J7zAi0jMFhm9PwTCi4SdY-internal" 'False) (C1 ('MetaCons "PackageMetadata" 'PrefixI 'True) (S1 ('MetaSel ('Just "pmIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PackageIdentifier) :*: S1 ('MetaSel ('Just "pmTreeKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TreeKey)))

toRawPM :: PackageMetadata -> RawPackageMetadata Source #

Convert package metadata to its "raw" equivalent.

Since: 0.1.0.0

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

Instances details
Show SnapshotCacheHash Source # 
Instance details

Defined in Pantry.Types

getGlobalHintsFile :: HasPantryConfig env => RIO env (Path Abs File) Source #

Get the path to the global hints cache file

bsToBlobKey :: ByteString -> BlobKey Source #

Creates BlobKey for an input ByteString

Since: 0.1.0.0

warnMissingCabalFile :: HasLogFunc env => RawPackageLocationImmutable -> RIO env () Source #

Warn if the package uses PCHpack.

Since: 0.4.0.0

connRDBMS :: SqlBackend -> Text #

A tag displaying what database the SqlBackend is for. Can be used to differentiate features in downstream libraries for different database backends.