pantry-0.10.0: Content addressable Haskell package management
Safe HaskellNone
LanguageHaskell2010

Pantry

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 or withPantryConfig'. See also PantryApp for a convenience approach to using pantry.

Since: 0.1.0.0

data PackageIndexConfig Source #

Configuration to securely download package metadata and contents. For most purposes, you'll want to use the default Hackage settings via defaultPackageIndexConfig.

NOTE It's highly recommended to only use the official Hackage server or a mirror. See https://github.com/commercialhaskell/stack/issues/4137.

Since: 0.6.0

Instances

Instances details
Show PackageIndexConfig 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> PackageIndexConfig -> ShowS

show :: PackageIndexConfig -> String

showList :: [PackageIndexConfig] -> ShowS

FromJSON (WithJSONWarnings PackageIndexConfig)

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

Constructors

HackageSecurityConfig 

Fields

Instances

Instances details
Show HackageSecurityConfig 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> HackageSecurityConfig -> ShowS

show :: HackageSecurityConfig -> String

showList :: [HackageSecurityConfig] -> ShowS

FromJSON (WithJSONWarnings HackageSecurityConfig)

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

defaultPackageIndexConfig :: PackageIndexConfig Source #

Default PackageIndexConfig value using the official Hackage server.

Since: 0.6.0

defaultDownloadPrefix :: Text Source #

The download prefix for the official Hackage server.

Since: 0.6.0

defaultHackageSecurityConfig :: HackageSecurityConfig Source #

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

Since: 0.7.0

defaultCasaRepoPrefix :: CasaRepoPrefix Source #

Default pull URL for Casa.

Since: 0.1.1.1

defaultCasaMaxPerRequest :: Int Source #

Default max keys to pull per request.

Since: 0.1.1.1

defaultSnapshotLocation :: SnapName -> RawSnapshotLocation Source #

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

Since: 0.5.0.0

defaultGlobalHintsLocation :: WantedCompiler -> GlobalHintsLocation Source #

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

Since: 0.9.4

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

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

-> PackageIndexConfig

Package index configuration. You probably want defaultPackageIndexConfig.

-> HpackExecutable

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

-> Int

Maximum connection count

-> CasaRepoPrefix

The casa pull URL e.g. https://casa.stackage.org/v1/pull.

-> Int

Max casa keys to pull per request.

-> (SnapName -> RawSnapshotLocation)

The location of snapshot synonyms

-> (WantedCompiler -> GlobalHintsLocation)

The location of global hints

-> (PantryConfig -> RIO env a)

What to do with the config

-> RIO env a 

Create a new PantryConfig with the given settings. For a version where Hpack's approach to overwriting Cabal files is configurable and the use of Casa (content-addressable storage archive) is optional, see withPantryConfig'.

For something easier to use in simple cases, see runPantryApp.

Since: 0.1.0.0

withPantryConfig' Source #

Arguments

:: HasLogFunc env 
=> Path Abs Dir

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

-> PackageIndexConfig

Package index configuration. You probably want defaultPackageIndexConfig.

-> HpackExecutable

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

-> Force

Should Hpack force the overwriting of a Cabal file that has been modified manually?

Since: 0.10.0

-> Int

Maximum connection count

-> Maybe (CasaRepoPrefix, Int)

Optionally, the Casa pull URL e.g. https://casa.fpcomplete.com and the maximum number of Casa keys to pull per request.

-> (SnapName -> RawSnapshotLocation)

The location of snapshot synonyms

-> (WantedCompiler -> GlobalHintsLocation)

The location of global hints

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

data HpackExecutable Source #

What to use for running hpack

Since: 0.1.0.0

Constructors

HpackBundled

Compiled in library

HpackCommand !FilePath

Executable at the provided path

Instances

Instances details
Read HpackExecutable 
Instance details

Defined in Pantry.Types

Show HpackExecutable 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> HpackExecutable -> ShowS

show :: HpackExecutable -> String

showList :: [HpackExecutable] -> ShowS

Eq HpackExecutable 
Instance details

Defined in Pantry.Types

Ord HpackExecutable 
Instance details

Defined in Pantry.Types

Convenience

data PantryApp Source #

Convenient data type that allows you to work with pantry more easily than using withPantryConfig or withPantryConfig' directly. Uses basically sane settings, like sharing a pantry directory with Stack.

You can use runPantryApp to use this. A simple example is:

{-# LANGUAGE OverloadedStrings #-}

module Main (main) where

-- From package Cabal-syntax
import Distribution.Types.Version ( mkVersion )
-- From package pantry
import Pantry
         ( CabalFileInfo (..), PackageIdentifierRevision (..), PantryApp
         , RawPackageLocationImmutable (..), loadPackageRaw, runPantryApp
         )
-- From package rio
import RIO ( RIO, liftIO )

main :: IO ()
main = runPantryApp myPantryApp

myPantryApp :: RIO PantryApp ()
myPantryApp = loadPackageRaw baseLocation >>= liftIO . print
 where
  baseVersion = mkVersion [4, 19, 0, 0]
  basePkgId = PackageIdentifierRevision "base" baseVersion CFILatest
  baseLocation = RPLIHackage basePkgId Nothing

Since: 0.1.0.0

Instances

Instances details
HasPantryConfig PantryApp Source # 
Instance details

Defined in Pantry

HasLogFunc PantryApp Source # 
Instance details

Defined in Pantry

Methods

logFuncL :: Lens' PantryApp LogFunc

HasProcessContext PantryApp Source # 
Instance details

Defined in Pantry

Methods

processContextL :: Lens' PantryApp ProcessContext

HasTerm PantryApp Source # 
Instance details

Defined in Pantry

Methods

useColorL :: Lens' PantryApp Bool

termWidthL :: Lens' PantryApp Int

HasStylesUpdate PantryApp Source # 
Instance details

Defined in Pantry

Methods

stylesUpdateL :: Lens' PantryApp StylesUpdate

runPantryApp :: MonadIO m => RIO PantryApp a -> m a Source #

Run some code against pantry using basic sane settings.

For testing, see runPantryAppClean.

Since: 0.1.0.0

runPantryAppClean :: MonadIO m => RIO PantryApp a -> m a Source #

Like runPantryApp, but uses an empty pantry directory instead of sharing with Stack. Useful for testing.

Since: 0.1.0.0

runPantryAppWith :: MonadIO m => Int -> CasaRepoPrefix -> Int -> RIO PantryApp a -> m a Source #

Run some code against pantry using basic sane settings.

For testing, see runPantryAppClean.

Since: 0.1.1.1

hpackExecutableL :: Lens' PantryConfig HpackExecutable Source #

Lens to view or modify the HpackExecutable of a PantryConfig.

Since: 0.1.0.0

hpackForceL :: Lens' PantryConfig Force Source #

Lens to view or modify the Force of a PantryConfig.

Since: 0.10.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 
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 

Instances

Instances details
Exception PantryException 
Instance details

Defined in Pantry.Types

Methods

toException :: PantryException -> SomeException

fromException :: SomeException -> Maybe PantryException

displayException :: PantryException -> String

Show PantryException 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> PantryException -> ShowS

show :: PantryException -> String

showList :: [PantryException] -> ShowS

Display PantryException 
Instance details

Defined in Pantry.Types

Methods

display :: PantryException -> Utf8Builder

textDisplay :: PantryException -> Text

Pretty PantryException 
Instance details

Defined in Pantry.Types

Methods

pretty :: PantryException -> StyleDoc

data Mismatch a Source #

Constructors

Mismatch 

Fields

Cabal types

data PackageName #

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

Methods

pretty :: PackageName -> Doc

prettyVersioned :: CabalSpecVersion -> PackageName -> Doc

Structured PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

structure :: Proxy PackageName -> Structure

structureHash' :: Tagged PackageName MD5

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

Defined in Distribution.Types.PackageName

Methods

fromString :: String -> PackageName

Generic PackageName 
Instance details

Defined in Distribution.Types.PackageName

Associated Types

type Rep PackageName 
Instance details

Defined in Distribution.Types.PackageName

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

Methods

from :: PackageName -> Rep PackageName x

to :: Rep PackageName x -> PackageName

Read PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

readsPrec :: Int -> ReadS PackageName

readList :: ReadS [PackageName]

readPrec :: ReadPrec PackageName

readListPrec :: ReadPrec [PackageName]

Show PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

showsPrec :: Int -> PackageName -> ShowS

show :: PackageName -> String

showList :: [PackageName] -> ShowS

Binary PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

put :: PackageName -> Put

get :: Get PackageName

putList :: [PackageName] -> Put

NFData PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

rnf :: PackageName -> ()

Eq PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

(==) :: PackageName -> PackageName -> Bool

(/=) :: PackageName -> PackageName -> Bool

Ord PackageName 
Instance details

Defined in Distribution.Types.PackageName

IsCabalString PackageName 
Instance details

Defined in Pantry.Types

Methods

cabalStringName :: proxy PackageName -> String

cabalStringParser :: String -> Maybe PackageName

type Rep PackageName 
Instance details

Defined in Distribution.Types.PackageName

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

data Version #

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

Methods

pretty :: Version -> Doc

prettyVersioned :: CabalSpecVersion -> Version -> Doc

Structured Version 
Instance details

Defined in Distribution.Types.Version

Methods

structure :: Proxy Version -> Structure

structureHash' :: Tagged Version MD5

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

Defined in Distribution.Types.Version

type Rep Version = D1 ('MetaData "Version" "Distribution.Types.Version" "Cabal-syntax-3.10.3.0-46ec" 'False) (C1 ('MetaCons "PV0" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 Word64)) :+: C1 ('MetaCons "PV1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int])))

Methods

from :: Version -> Rep Version x

to :: Rep Version x -> Version

Read Version 
Instance details

Defined in Distribution.Types.Version

Methods

readsPrec :: Int -> ReadS Version

readList :: ReadS [Version]

readPrec :: ReadPrec Version

readListPrec :: ReadPrec [Version]

Show Version 
Instance details

Defined in Distribution.Types.Version

Methods

showsPrec :: Int -> Version -> ShowS

show :: Version -> String

showList :: [Version] -> ShowS

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

Methods

compare :: Version -> Version -> Ordering

(<) :: Version -> Version -> Bool

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

(>) :: Version -> Version -> Bool

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

max :: Version -> Version -> Version

min :: Version -> Version -> Version

IsCabalString Version 
Instance details

Defined in Pantry.Types

Methods

cabalStringName :: proxy Version -> String

cabalStringParser :: String -> Maybe Version

type Rep Version 
Instance details

Defined in Distribution.Types.Version

type Rep Version = D1 ('MetaData "Version" "Distribution.Types.Version" "Cabal-syntax-3.10.3.0-46ec" 'False) (C1 ('MetaCons "PV0" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 Word64)) :+: C1 ('MetaCons "PV1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int])))

data FlagName #

Instances

Instances details
Parsec FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

parsec :: CabalParsing m => m FlagName

Pretty FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

pretty :: FlagName -> Doc

prettyVersioned :: CabalSpecVersion -> FlagName -> Doc

Structured FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

structure :: Proxy FlagName -> Structure

structureHash' :: Tagged FlagName MD5

Data FlagName 
Instance details

Defined in Distribution.Types.Flag

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 :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FlagName -> r

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

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

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

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

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

IsString FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

fromString :: String -> FlagName

Generic FlagName 
Instance details

Defined in Distribution.Types.Flag

Associated Types

type Rep FlagName 
Instance details

Defined in Distribution.Types.Flag

type Rep FlagName = D1 ('MetaData "FlagName" "Distribution.Types.Flag" "Cabal-syntax-3.10.3.0-46ec" 'True) (C1 ('MetaCons "FlagName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortText)))

Methods

from :: FlagName -> Rep FlagName x

to :: Rep FlagName x -> FlagName

Read FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

readsPrec :: Int -> ReadS FlagName

readList :: ReadS [FlagName]

readPrec :: ReadPrec FlagName

readListPrec :: ReadPrec [FlagName]

Show FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

showsPrec :: Int -> FlagName -> ShowS

show :: FlagName -> String

showList :: [FlagName] -> ShowS

Binary FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

put :: FlagName -> Put

get :: Get FlagName

putList :: [FlagName] -> Put

NFData FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

rnf :: FlagName -> ()

Eq FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

(==) :: FlagName -> FlagName -> Bool

(/=) :: FlagName -> FlagName -> Bool

Ord FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

compare :: FlagName -> FlagName -> Ordering

(<) :: FlagName -> FlagName -> Bool

(<=) :: FlagName -> FlagName -> Bool

(>) :: FlagName -> FlagName -> Bool

(>=) :: FlagName -> FlagName -> Bool

max :: FlagName -> FlagName -> FlagName

min :: FlagName -> FlagName -> FlagName

IsCabalString FlagName 
Instance details

Defined in Pantry.Types

Methods

cabalStringName :: proxy FlagName -> String

cabalStringParser :: String -> Maybe FlagName

type Rep FlagName 
Instance details

Defined in Distribution.Types.Flag

type Rep FlagName = D1 ('MetaData "FlagName" "Distribution.Types.Flag" "Cabal-syntax-3.10.3.0-46ec" 'True) (C1 ('MetaCons "FlagName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortText)))

data PackageIdentifier #

Instances

Instances details
Package PackageIdentifier 
Instance details

Defined in Distribution.Package

Parsec PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Methods

parsec :: CabalParsing m => m PackageIdentifier

Pretty PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Methods

pretty :: PackageIdentifier -> Doc

prettyVersioned :: CabalSpecVersion -> PackageIdentifier -> Doc

Structured PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Methods

structure :: Proxy PackageIdentifier -> Structure

structureHash' :: Tagged PackageIdentifier MD5

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

Defined in Distribution.Types.PackageId

type Rep PackageIdentifier = D1 ('MetaData "PackageIdentifier" "Distribution.Types.PackageId" "Cabal-syntax-3.10.3.0-46ec" 'False) (C1 ('MetaCons "PackageIdentifier" 'PrefixI 'True) (S1 ('MetaSel ('Just "pkgName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageName) :*: S1 ('MetaSel ('Just "pkgVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)))
Read PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Show PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Methods

showsPrec :: Int -> PackageIdentifier -> ShowS

show :: PackageIdentifier -> String

showList :: [PackageIdentifier] -> ShowS

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

IsCabalString PackageIdentifier 
Instance details

Defined in Pantry.Types

Methods

cabalStringName :: proxy PackageIdentifier -> String

cabalStringParser :: String -> Maybe PackageIdentifier

type Rep PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

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

Hpack types

data Force Source #

Constructors

Force 
NoForce 

Instances

Instances details
Show Force 
Instance details

Defined in Hpack.Options

Methods

showsPrec :: Int -> Force -> ShowS

show :: Force -> String

showList :: [Force] -> ShowS

Eq Force 
Instance details

Defined in Hpack.Options

Methods

(==) :: Force -> Force -> Bool

(/=) :: Force -> Force -> Bool

Files

newtype FileSize Source #

File size in bytes

Since: 0.1.0.0

Constructors

FileSize Word 

Instances

Instances details
FromJSON FileSize 
Instance details

Defined in Pantry.Types

Methods

parseJSON :: Value -> Parser FileSize

parseJSONList :: Value -> Parser [FileSize]

omittedField :: Maybe FileSize

ToJSON FileSize 
Instance details

Defined in Pantry.Types

Methods

toJSON :: FileSize -> Value

toEncoding :: FileSize -> Encoding

toJSONList :: [FileSize] -> Value

toEncodingList :: [FileSize] -> Encoding

omitField :: FileSize -> Bool

Generic FileSize 
Instance details

Defined in Pantry.Types

Associated Types

type Rep FileSize 
Instance details

Defined in Pantry.Types

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

Methods

from :: FileSize -> Rep FileSize x

to :: Rep FileSize x -> FileSize

Show FileSize 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> FileSize -> ShowS

show :: FileSize -> String

showList :: [FileSize] -> ShowS

NFData FileSize 
Instance details

Defined in Pantry.Types

Methods

rnf :: FileSize -> ()

Eq FileSize 
Instance details

Defined in Pantry.Types

Methods

(==) :: FileSize -> FileSize -> Bool

(/=) :: FileSize -> FileSize -> Bool

Ord FileSize 
Instance details

Defined in Pantry.Types

Methods

compare :: FileSize -> FileSize -> Ordering

(<) :: FileSize -> FileSize -> Bool

(<=) :: FileSize -> FileSize -> Bool

(>) :: FileSize -> FileSize -> Bool

(>=) :: FileSize -> FileSize -> Bool

max :: FileSize -> FileSize -> FileSize

min :: FileSize -> FileSize -> FileSize

Hashable FileSize 
Instance details

Defined in Pantry.Types

Methods

hashWithSalt :: Int -> FileSize -> Int

hash :: FileSize -> Int

PersistField FileSize 
Instance details

Defined in Pantry.Types

Methods

toPersistValue :: FileSize -> PersistValue

fromPersistValue :: PersistValue -> Either Text FileSize

PersistFieldSql FileSize 
Instance details

Defined in Pantry.Types

Methods

sqlType :: Proxy FileSize -> SqlType

Display FileSize 
Instance details

Defined in Pantry.Types

Methods

display :: FileSize -> Utf8Builder

textDisplay :: FileSize -> Text

type Rep FileSize 
Instance details

Defined in Pantry.Types

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

Instances details
FromJSON RelFilePath 
Instance details

Defined in Pantry.Types

ToJSON RelFilePath 
Instance details

Defined in Pantry.Types

Generic RelFilePath 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RelFilePath 
Instance details

Defined in Pantry.Types

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

Methods

from :: RelFilePath -> Rep RelFilePath x

to :: Rep RelFilePath x -> RelFilePath

Show RelFilePath 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> RelFilePath -> ShowS

show :: RelFilePath -> String

showList :: [RelFilePath] -> ShowS

NFData RelFilePath 
Instance details

Defined in Pantry.Types

Methods

rnf :: RelFilePath -> ()

Eq RelFilePath 
Instance details

Defined in Pantry.Types

Methods

(==) :: RelFilePath -> RelFilePath -> Bool

(/=) :: RelFilePath -> RelFilePath -> Bool

Ord RelFilePath 
Instance details

Defined in Pantry.Types

Display RelFilePath 
Instance details

Defined in Pantry.Types

Methods

display :: RelFilePath -> Utf8Builder

textDisplay :: RelFilePath -> Text

type Rep RelFilePath 
Instance details

Defined in Pantry.Types

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

Instances details
Generic (ResolvedPath t) 
Instance details

Defined in Pantry.Types

Associated Types

type Rep (ResolvedPath t) 
Instance details

Defined in Pantry.Types

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

Methods

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

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

Show (ResolvedPath t) 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> ResolvedPath t -> ShowS

show :: ResolvedPath t -> String

showList :: [ResolvedPath t] -> ShowS

NFData (ResolvedPath t) 
Instance details

Defined in Pantry.Types

Methods

rnf :: ResolvedPath t -> ()

Eq (ResolvedPath t) 
Instance details

Defined in Pantry.Types

Methods

(==) :: ResolvedPath t -> ResolvedPath t -> Bool

(/=) :: ResolvedPath t -> ResolvedPath t -> Bool

Ord (ResolvedPath t) 
Instance details

Defined in Pantry.Types

Methods

compare :: ResolvedPath t -> ResolvedPath t -> Ordering

(<) :: ResolvedPath t -> ResolvedPath t -> Bool

(<=) :: ResolvedPath t -> ResolvedPath t -> Bool

(>) :: ResolvedPath t -> ResolvedPath t -> Bool

(>=) :: ResolvedPath t -> ResolvedPath t -> Bool

max :: ResolvedPath t -> ResolvedPath t -> ResolvedPath t

min :: ResolvedPath t -> ResolvedPath t -> ResolvedPath t

type Rep (ResolvedPath t) 
Instance details

Defined in Pantry.Types

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

Defined in Pantry.Types

Methods

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

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

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

Defined in Pantry.Types

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

Defined in Pantry.Types

FromJSON (WithJSONWarnings (Unresolved GlobalHintsLocation)) 
Instance details

Defined in Pantry.Types

FromJSON (WithJSONWarnings (Unresolved PackageLocationImmutable)) 
Instance details

Defined in Pantry.Types

FromJSON (WithJSONWarnings (Unresolved RawSnapshotLayer)) 
Instance details

Defined in Pantry.Types

FromJSON (WithJSONWarnings (Unresolved RawSnapshotLocation)) 
Instance details

Defined in Pantry.Types

FromJSON (WithJSONWarnings (Unresolved SnapshotLocation)) 
Instance details

Defined in Pantry.Types

data SafeFilePath Source #

Instances

Instances details
Show SafeFilePath 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> SafeFilePath -> ShowS

show :: SafeFilePath -> String

showList :: [SafeFilePath] -> ShowS

Eq SafeFilePath 
Instance details

Defined in Pantry.Types

Methods

(==) :: SafeFilePath -> SafeFilePath -> Bool

(/=) :: SafeFilePath -> SafeFilePath -> Bool

Ord SafeFilePath 
Instance details

Defined in Pantry.Types

PersistField SafeFilePath 
Instance details

Defined in Pantry.Types

Methods

toPersistValue :: SafeFilePath -> PersistValue

fromPersistValue :: PersistValue -> Either Text SafeFilePath

PersistFieldSql SafeFilePath 
Instance details

Defined in Pantry.Types

Methods

sqlType :: Proxy SafeFilePath -> SqlType

Display SafeFilePath 
Instance details

Defined in Pantry.Types

Methods

display :: SafeFilePath -> Utf8Builder

textDisplay :: SafeFilePath -> Text

Cryptography

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

Defined in Pantry.SHA256

Methods

parseJSON :: Value -> Parser SHA256

parseJSONList :: Value -> Parser [SHA256]

omittedField :: Maybe SHA256

ToJSON SHA256 
Instance details

Defined in Pantry.SHA256

Methods

toJSON :: SHA256 -> Value

toEncoding :: SHA256 -> Encoding

toJSONList :: [SHA256] -> Value

toEncodingList :: [SHA256] -> Encoding

omitField :: SHA256 -> Bool

Data SHA256 
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 
Instance details

Defined in Pantry.SHA256

Associated Types

type Rep SHA256 
Instance details

Defined in Pantry.SHA256

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

Methods

from :: SHA256 -> Rep SHA256 x

to :: Rep SHA256 x -> SHA256

Show SHA256 
Instance details

Defined in Pantry.SHA256

Methods

showsPrec :: Int -> SHA256 -> ShowS

show :: SHA256 -> String

showList :: [SHA256] -> ShowS

NFData SHA256 
Instance details

Defined in Pantry.SHA256

Methods

rnf :: SHA256 -> ()

Eq SHA256 
Instance details

Defined in Pantry.SHA256

Methods

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

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

Ord SHA256 
Instance details

Defined in Pantry.SHA256

Methods

compare :: SHA256 -> SHA256 -> Ordering

(<) :: SHA256 -> SHA256 -> Bool

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

(>) :: SHA256 -> SHA256 -> Bool

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

max :: SHA256 -> SHA256 -> SHA256

min :: SHA256 -> SHA256 -> SHA256

Hashable SHA256 
Instance details

Defined in Pantry.SHA256

Methods

hashWithSalt :: Int -> SHA256 -> Int

hash :: SHA256 -> Int

PersistField SHA256 
Instance details

Defined in Pantry.SHA256

Methods

toPersistValue :: SHA256 -> PersistValue

fromPersistValue :: PersistValue -> Either Text SHA256

PersistFieldSql SHA256 
Instance details

Defined in Pantry.SHA256

Methods

sqlType :: Proxy SHA256 -> SqlType

Display SHA256 
Instance details

Defined in Pantry.SHA256

Methods

display :: SHA256 -> Utf8Builder

textDisplay :: SHA256 -> Text

type Rep SHA256 
Instance details

Defined in Pantry.SHA256

type Rep SHA256 = D1 ('MetaData "SHA256" "Pantry.SHA256" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" '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

Instances details
FromJSON TreeKey 
Instance details

Defined in Pantry.Types

Methods

parseJSON :: Value -> Parser TreeKey

parseJSONList :: Value -> Parser [TreeKey]

omittedField :: Maybe TreeKey

ToJSON TreeKey 
Instance details

Defined in Pantry.Types

Methods

toJSON :: TreeKey -> Value

toEncoding :: TreeKey -> Encoding

toJSONList :: [TreeKey] -> Value

toEncodingList :: [TreeKey] -> Encoding

omitField :: TreeKey -> Bool

Generic TreeKey 
Instance details

Defined in Pantry.Types

Associated Types

type Rep TreeKey 
Instance details

Defined in Pantry.Types

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

Methods

from :: TreeKey -> Rep TreeKey x

to :: Rep TreeKey x -> TreeKey

Show TreeKey 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> TreeKey -> ShowS

show :: TreeKey -> String

showList :: [TreeKey] -> ShowS

NFData TreeKey 
Instance details

Defined in Pantry.Types

Methods

rnf :: TreeKey -> ()

Eq TreeKey 
Instance details

Defined in Pantry.Types

Methods

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

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

Ord TreeKey 
Instance details

Defined in Pantry.Types

Methods

compare :: TreeKey -> TreeKey -> Ordering

(<) :: TreeKey -> TreeKey -> Bool

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

(>) :: TreeKey -> TreeKey -> Bool

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

max :: TreeKey -> TreeKey -> TreeKey

min :: TreeKey -> TreeKey -> TreeKey

Display TreeKey 
Instance details

Defined in Pantry.Types

Methods

display :: TreeKey -> Utf8Builder

textDisplay :: TreeKey -> Text

type Rep TreeKey 
Instance details

Defined in Pantry.Types

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

Instances details
FromJSON BlobKey 
Instance details

Defined in Pantry.Types

Methods

parseJSON :: Value -> Parser BlobKey

parseJSONList :: Value -> Parser [BlobKey]

omittedField :: Maybe BlobKey

ToJSON BlobKey 
Instance details

Defined in Pantry.Types

Methods

toJSON :: BlobKey -> Value

toEncoding :: BlobKey -> Encoding

toJSONList :: [BlobKey] -> Value

toEncodingList :: [BlobKey] -> Encoding

omitField :: BlobKey -> Bool

Generic BlobKey 
Instance details

Defined in Pantry.Types

Associated Types

type Rep BlobKey 
Instance details

Defined in Pantry.Types

type Rep BlobKey = D1 ('MetaData "BlobKey" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" 'False) (C1 ('MetaCons "BlobKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SHA256) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 FileSize)))

Methods

from :: BlobKey -> Rep BlobKey x

to :: Rep BlobKey x -> BlobKey

Show BlobKey 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> BlobKey -> ShowS

show :: BlobKey -> String

showList :: [BlobKey] -> ShowS

NFData BlobKey 
Instance details

Defined in Pantry.Types

Methods

rnf :: BlobKey -> ()

Eq BlobKey 
Instance details

Defined in Pantry.Types

Methods

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

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

Ord BlobKey 
Instance details

Defined in Pantry.Types

Methods

compare :: BlobKey -> BlobKey -> Ordering

(<) :: BlobKey -> BlobKey -> Bool

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

(>) :: BlobKey -> BlobKey -> Bool

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

max :: BlobKey -> BlobKey -> BlobKey

min :: BlobKey -> BlobKey -> BlobKey

Display BlobKey 
Instance details

Defined in Pantry.Types

Methods

display :: BlobKey -> Utf8Builder

textDisplay :: BlobKey -> Text

type Rep BlobKey 
Instance details

Defined in Pantry.Types

type Rep BlobKey = D1 ('MetaData "BlobKey" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" 'False) (C1 ('MetaCons "BlobKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SHA256) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 FileSize)))

Packages

data RawPackageMetadata Source #

Metadata provided by a config file for archives and repos. This information can be used for optimized lookups of information like package identifiers, or for validating that the user configuration has the expected information.

Since: 0.1.0.0

Constructors

RawPackageMetadata 

Fields

Instances

Instances details
Generic RawPackageMetadata 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RawPackageMetadata 
Instance details

Defined in Pantry.Types

type Rep RawPackageMetadata = D1 ('MetaData "RawPackageMetadata" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-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)))))
Show RawPackageMetadata 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> RawPackageMetadata -> ShowS

show :: RawPackageMetadata -> String

showList :: [RawPackageMetadata] -> ShowS

NFData RawPackageMetadata 
Instance details

Defined in Pantry.Types

Methods

rnf :: RawPackageMetadata -> ()

Eq RawPackageMetadata 
Instance details

Defined in Pantry.Types

Ord RawPackageMetadata 
Instance details

Defined in Pantry.Types

Display RawPackageMetadata 
Instance details

Defined in Pantry.Types

Methods

display :: RawPackageMetadata -> Utf8Builder

textDisplay :: RawPackageMetadata -> Text

type Rep RawPackageMetadata 
Instance details

Defined in Pantry.Types

type Rep RawPackageMetadata = D1 ('MetaData "RawPackageMetadata" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-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 
Instance details

Defined in Pantry.Types

Associated Types

type Rep PackageMetadata 
Instance details

Defined in Pantry.Types

type Rep PackageMetadata = D1 ('MetaData "PackageMetadata" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-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)))
Show PackageMetadata 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> PackageMetadata -> ShowS

show :: PackageMetadata -> String

showList :: [PackageMetadata] -> ShowS

NFData PackageMetadata 
Instance details

Defined in Pantry.Types

Methods

rnf :: PackageMetadata -> ()

Eq PackageMetadata 
Instance details

Defined in Pantry.Types

Ord PackageMetadata 
Instance details

Defined in Pantry.Types

Display PackageMetadata 
Instance details

Defined in Pantry.Types

Methods

display :: PackageMetadata -> Utf8Builder

textDisplay :: PackageMetadata -> Text

type Rep PackageMetadata 
Instance details

Defined in Pantry.Types

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

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

Defined in Pantry.Types

Methods

showsPrec :: Int -> Package -> ShowS

show :: Package -> String

showList :: [Package] -> ShowS

Eq Package 
Instance details

Defined in Pantry.Types

Methods

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

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

Ord Package 
Instance details

Defined in Pantry.Types

Methods

compare :: Package -> Package -> Ordering

(<) :: Package -> Package -> Bool

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

(>) :: Package -> Package -> Bool

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

max :: Package -> Package -> Package

min :: Package -> Package -> Package

Hackage

data CabalFileInfo Source #

How to choose a cabal file for a package from Hackage. This is to work with Hackage cabal file revisions, which makes PackageIdentifier insufficient for specifying a package from Hackage.

Since: 0.1.0.0

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

Defined in Pantry.Types

Associated Types

type Rep CabalFileInfo 
Instance details

Defined in Pantry.Types

type Rep CabalFileInfo = D1 ('MetaData "CabalFileInfo" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-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 'DecidedUnpack) (Rec0 Revision))))
Show CabalFileInfo 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> CabalFileInfo -> ShowS

show :: CabalFileInfo -> String

showList :: [CabalFileInfo] -> ShowS

NFData CabalFileInfo 
Instance details

Defined in Pantry.Types

Methods

rnf :: CabalFileInfo -> ()

Eq CabalFileInfo 
Instance details

Defined in Pantry.Types

Ord CabalFileInfo 
Instance details

Defined in Pantry.Types

Hashable CabalFileInfo 
Instance details

Defined in Pantry.Types

Methods

hashWithSalt :: Int -> CabalFileInfo -> Int

hash :: CabalFileInfo -> Int

Display CabalFileInfo 
Instance details

Defined in Pantry.Types

Methods

display :: CabalFileInfo -> Utf8Builder

textDisplay :: CabalFileInfo -> Text

type Rep CabalFileInfo 
Instance details

Defined in Pantry.Types

type Rep CabalFileInfo = D1 ('MetaData "CabalFileInfo" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-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 'DecidedUnpack) (Rec0 Revision))))

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

Defined in Pantry.Types

Associated Types

type Rep Revision 
Instance details

Defined in Pantry.Types

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

Methods

from :: Revision -> Rep Revision x

to :: Rep Revision x -> Revision

Show Revision 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> Revision -> ShowS

show :: Revision -> String

showList :: [Revision] -> ShowS

NFData Revision 
Instance details

Defined in Pantry.Types

Methods

rnf :: Revision -> ()

Eq Revision 
Instance details

Defined in Pantry.Types

Methods

(==) :: Revision -> Revision -> Bool

(/=) :: Revision -> Revision -> Bool

Ord Revision 
Instance details

Defined in Pantry.Types

Methods

compare :: Revision -> Revision -> Ordering

(<) :: Revision -> Revision -> Bool

(<=) :: Revision -> Revision -> Bool

(>) :: Revision -> Revision -> Bool

(>=) :: Revision -> Revision -> Bool

max :: Revision -> Revision -> Revision

min :: Revision -> Revision -> Revision

Hashable Revision 
Instance details

Defined in Pantry.Types

Methods

hashWithSalt :: Int -> Revision -> Int

hash :: Revision -> Int

PersistField Revision 
Instance details

Defined in Pantry.Types

Methods

toPersistValue :: Revision -> PersistValue

fromPersistValue :: PersistValue -> Either Text Revision

PersistFieldSql Revision 
Instance details

Defined in Pantry.Types

Methods

sqlType :: Proxy Revision -> SqlType

Display Revision 
Instance details

Defined in Pantry.Types

Methods

display :: Revision -> Utf8Builder

textDisplay :: Revision -> Text

type Rep Revision 
Instance details

Defined in Pantry.Types

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

Instances details
FromJSON PackageIdentifierRevision 
Instance details

Defined in Pantry.Types

ToJSON PackageIdentifierRevision 
Instance details

Defined in Pantry.Types

Generic PackageIdentifierRevision 
Instance details

Defined in Pantry.Types

Associated Types

type Rep PackageIdentifierRevision 
Instance details

Defined in Pantry.Types

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

Defined in Pantry.Types

NFData PackageIdentifierRevision 
Instance details

Defined in Pantry.Types

Eq PackageIdentifierRevision 
Instance details

Defined in Pantry.Types

Ord PackageIdentifierRevision 
Instance details

Defined in Pantry.Types

Display PackageIdentifierRevision 
Instance details

Defined in Pantry.Types

type Rep PackageIdentifierRevision 
Instance details

Defined in Pantry.Types

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

data UsePreferredVersions Source #

Should we pay attention to Hackage's preferred versions?

Since: 0.1.0.0

Instances

Instances details
Show UsePreferredVersions Source # 
Instance details

Defined in Pantry.Hackage

Methods

showsPrec :: Int -> UsePreferredVersions -> ShowS

show :: UsePreferredVersions -> String

showList :: [UsePreferredVersions] -> ShowS

Archives

data RawArchive Source #

A raw package archive, specified by a user, could have no hash and file size information.

Since: 0.1.0.0

Constructors

RawArchive 

Fields

  • raLocation :: !ArchiveLocation

    Location of the archive

    Since: 0.1.0.0

  • raHash :: !(Maybe SHA256)

    Cryptographic hash of the archive file

    Since: 0.1.0.0

  • raSize :: !(Maybe FileSize)

    Size of the archive file

    Since: 0.1.0.0

  • raSubdir :: !Text

    Subdirectory within the archive to get the package from.

    Since: 0.1.0.0

Instances

Instances details
Generic RawArchive 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RawArchive 
Instance details

Defined in Pantry.Types

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

Methods

from :: RawArchive -> Rep RawArchive x

to :: Rep RawArchive x -> RawArchive

Show RawArchive 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> RawArchive -> ShowS

show :: RawArchive -> String

showList :: [RawArchive] -> ShowS

NFData RawArchive 
Instance details

Defined in Pantry.Types

Methods

rnf :: RawArchive -> ()

Eq RawArchive 
Instance details

Defined in Pantry.Types

Methods

(==) :: RawArchive -> RawArchive -> Bool

(/=) :: RawArchive -> RawArchive -> Bool

Ord RawArchive 
Instance details

Defined in Pantry.Types

type Rep RawArchive 
Instance details

Defined in Pantry.Types

type Rep RawArchive = D1 ('MetaData "RawArchive" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-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 
Instance details

Defined in Pantry.Types

Associated Types

type Rep Archive 
Instance details

Defined in Pantry.Types

type Rep Archive = D1 ('MetaData "Archive" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-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 'DecidedUnpack) (Rec0 FileSize) :*: S1 ('MetaSel ('Just "archiveSubdir") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))))

Methods

from :: Archive -> Rep Archive x

to :: Rep Archive x -> Archive

Show Archive 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> Archive -> ShowS

show :: Archive -> String

showList :: [Archive] -> ShowS

NFData Archive 
Instance details

Defined in Pantry.Types

Methods

rnf :: Archive -> ()

Eq Archive 
Instance details

Defined in Pantry.Types

Methods

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

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

Ord Archive 
Instance details

Defined in Pantry.Types

Methods

compare :: Archive -> Archive -> Ordering

(<) :: Archive -> Archive -> Bool

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

(>) :: Archive -> Archive -> Bool

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

max :: Archive -> Archive -> Archive

min :: Archive -> Archive -> Archive

type Rep Archive 
Instance details

Defined in Pantry.Types

type Rep Archive = D1 ('MetaData "Archive" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-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 'DecidedUnpack) (Rec0 FileSize) :*: S1 ('MetaSel ('Just "archiveSubdir") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))))

data ArchiveLocation Source #

Location that an archive is stored at

Since: 0.1.0.0

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

Defined in Pantry.Types

Associated Types

type Rep ArchiveLocation 
Instance details

Defined in Pantry.Types

type Rep ArchiveLocation = D1 ('MetaData "ArchiveLocation" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-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))))
Show ArchiveLocation 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> ArchiveLocation -> ShowS

show :: ArchiveLocation -> String

showList :: [ArchiveLocation] -> ShowS

NFData ArchiveLocation 
Instance details

Defined in Pantry.Types

Methods

rnf :: ArchiveLocation -> ()

Eq ArchiveLocation 
Instance details

Defined in Pantry.Types

Ord ArchiveLocation 
Instance details

Defined in Pantry.Types

Display ArchiveLocation 
Instance details

Defined in Pantry.Types

Methods

display :: ArchiveLocation -> Utf8Builder

textDisplay :: ArchiveLocation -> Text

Pretty ArchiveLocation 
Instance details

Defined in Pantry.Types

Methods

pretty :: ArchiveLocation -> StyleDoc

type Rep ArchiveLocation 
Instance details

Defined in Pantry.Types

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

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

Instances details
Generic Repo 
Instance details

Defined in Pantry.Types

Associated Types

type Rep Repo 
Instance details

Defined in Pantry.Types

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

Methods

from :: Repo -> Rep Repo x

to :: Rep Repo x -> Repo

Show Repo 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> Repo -> ShowS

show :: Repo -> String

showList :: [Repo] -> ShowS

NFData Repo 
Instance details

Defined in Pantry.Types

Methods

rnf :: Repo -> ()

Eq Repo 
Instance details

Defined in Pantry.Types

Methods

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

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

Ord Repo 
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 
Instance details

Defined in Pantry.Types

Methods

display :: Repo -> Utf8Builder

textDisplay :: Repo -> Text

type Rep Repo 
Instance details

Defined in Pantry.Types

type Rep Repo = D1 ('MetaData "Repo" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-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 RepoType Source #

The type of a source control repository.

Since: 0.1.0.0

Constructors

RepoGit 
RepoHg 

Instances

Instances details
Generic RepoType 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RepoType 
Instance details

Defined in Pantry.Types

type Rep RepoType = D1 ('MetaData "RepoType" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" 'False) (C1 ('MetaCons "RepoGit" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RepoHg" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: RepoType -> Rep RepoType x

to :: Rep RepoType x -> RepoType

Show RepoType 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> RepoType -> ShowS

show :: RepoType -> String

showList :: [RepoType] -> ShowS

NFData RepoType 
Instance details

Defined in Pantry.Types

Methods

rnf :: RepoType -> ()

Eq RepoType 
Instance details

Defined in Pantry.Types

Methods

(==) :: RepoType -> RepoType -> Bool

(/=) :: RepoType -> RepoType -> Bool

Ord RepoType 
Instance details

Defined in Pantry.Types

Methods

compare :: RepoType -> RepoType -> Ordering

(<) :: RepoType -> RepoType -> Bool

(<=) :: RepoType -> RepoType -> Bool

(>) :: RepoType -> RepoType -> Bool

(>=) :: RepoType -> RepoType -> Bool

max :: RepoType -> RepoType -> RepoType

min :: RepoType -> RepoType -> RepoType

PersistField RepoType 
Instance details

Defined in Pantry.Types

Methods

toPersistValue :: RepoType -> PersistValue

fromPersistValue :: PersistValue -> Either Text RepoType

PersistFieldSql RepoType 
Instance details

Defined in Pantry.Types

Methods

sqlType :: Proxy RepoType -> SqlType

type Rep RepoType 
Instance details

Defined in Pantry.Types

type Rep RepoType = D1 ('MetaData "RepoType" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" 'False) (C1 ('MetaCons "RepoGit" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RepoHg" 'PrefixI 'False) (U1 :: Type -> Type))

data SimpleRepo Source #

Repository without subdirectory information.

Since: 0.5.3

Constructors

SimpleRepo 

Fields

Instances

Instances details
Generic SimpleRepo 
Instance details

Defined in Pantry.Types

Associated Types

type Rep SimpleRepo 
Instance details

Defined in Pantry.Types

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

Methods

from :: SimpleRepo -> Rep SimpleRepo x

to :: Rep SimpleRepo x -> SimpleRepo

Show SimpleRepo 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> SimpleRepo -> ShowS

show :: SimpleRepo -> String

showList :: [SimpleRepo] -> ShowS

Eq SimpleRepo 
Instance details

Defined in Pantry.Types

Methods

(==) :: SimpleRepo -> SimpleRepo -> Bool

(/=) :: SimpleRepo -> SimpleRepo -> Bool

Ord SimpleRepo 
Instance details

Defined in Pantry.Types

Display SimpleRepo 
Instance details

Defined in Pantry.Types

Methods

display :: SimpleRepo -> Utf8Builder

textDisplay :: SimpleRepo -> Text

type Rep SimpleRepo 
Instance details

Defined in Pantry.Types

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

withRepo :: (HasLogFunc env, HasProcessContext env) => SimpleRepo -> RIO env a -> RIO env a Source #

Clone the repository (and, in the case of Git and if necessary, fetch the specific commit) and execute the action with the working directory set to the repository root.

Since: 0.1.0.0

fetchRepos :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => [(Repo, PackageMetadata)] -> RIO env () Source #

Fetch the given repositories at once and populate the pantry database.

Since: 0.5.3

fetchReposRaw :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => [(Repo, RawPackageMetadata)] -> RIO env () Source #

Like fetchRepos, except with RawPackageMetadata instead of PackageMetadata.

Since: 0.5.3

Package location

data RawPackageLocation Source #

Location to load a package from. Can either be immutable (see PackageLocationImmutable) or a local directory which is expected to change over time. Raw version doesn't include exact package version (e.g. could refer to the latest revision on Hackage)

Since: 0.1.0.0

Instances

Instances details
ToJSON RawPackageLocation 
Instance details

Defined in Pantry.Types

Generic RawPackageLocation 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RawPackageLocation 
Instance details

Defined in Pantry.Types

type Rep RawPackageLocation = D1 ('MetaData "RawPackageLocation" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-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))))
Show RawPackageLocation 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> RawPackageLocation -> ShowS

show :: RawPackageLocation -> String

showList :: [RawPackageLocation] -> ShowS

NFData RawPackageLocation 
Instance details

Defined in Pantry.Types

Methods

rnf :: RawPackageLocation -> ()

Eq RawPackageLocation 
Instance details

Defined in Pantry.Types

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

Defined in Pantry.Types

type Rep RawPackageLocation 
Instance details

Defined in Pantry.Types

type Rep RawPackageLocation = D1 ('MetaData "RawPackageLocation" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-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 
Instance details

Defined in Pantry.Types

Associated Types

type Rep PackageLocation 
Instance details

Defined in Pantry.Types

type Rep PackageLocation = D1 ('MetaData "PackageLocation" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-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))))
Show PackageLocation 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> PackageLocation -> ShowS

show :: PackageLocation -> String

showList :: [PackageLocation] -> ShowS

NFData PackageLocation 
Instance details

Defined in Pantry.Types

Methods

rnf :: PackageLocation -> ()

Eq PackageLocation 
Instance details

Defined in Pantry.Types

Display PackageLocation 
Instance details

Defined in Pantry.Types

Methods

display :: PackageLocation -> Utf8Builder

textDisplay :: PackageLocation -> Text

type Rep PackageLocation 
Instance details

Defined in Pantry.Types

type Rep PackageLocation = D1 ('MetaData "PackageLocation" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-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 
Instance details

Defined in Pantry.Types

Generic RawPackageLocationImmutable 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RawPackageLocationImmutable 
Instance details

Defined in Pantry.Types

type Rep RawPackageLocationImmutable = D1 ('MetaData "RawPackageLocationImmutable" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" 'False) (C1 ('MetaCons "RPLIHackage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PackageIdentifierRevision) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe TreeKey))) :+: (C1 ('MetaCons "RPLIArchive" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RawArchive) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RawPackageMetadata)) :+: C1 ('MetaCons "RPLIRepo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Repo) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RawPackageMetadata))))
Show RawPackageLocationImmutable 
Instance details

Defined in Pantry.Types

NFData RawPackageLocationImmutable 
Instance details

Defined in Pantry.Types

Eq RawPackageLocationImmutable 
Instance details

Defined in Pantry.Types

Ord RawPackageLocationImmutable 
Instance details

Defined in Pantry.Types

Display RawPackageLocationImmutable 
Instance details

Defined in Pantry.Types

Pretty RawPackageLocationImmutable 
Instance details

Defined in Pantry.Types

Methods

pretty :: RawPackageLocationImmutable -> StyleDoc

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

Defined in Pantry.Types

type Rep RawPackageLocationImmutable 
Instance details

Defined in Pantry.Types

type Rep RawPackageLocationImmutable = D1 ('MetaData "RawPackageLocationImmutable" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" 'False) (C1 ('MetaCons "RPLIHackage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PackageIdentifierRevision) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe TreeKey))) :+: (C1 ('MetaCons "RPLIArchive" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RawArchive) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RawPackageMetadata)) :+: C1 ('MetaCons "RPLIRepo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Repo) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RawPackageMetadata))))

data PackageLocationImmutable Source #

Location for remote packages or archives assumed to be immutable.

Since: 0.1.0.0

Instances

Instances details
ToJSON PackageLocationImmutable 
Instance details

Defined in Pantry.Types

Generic PackageLocationImmutable 
Instance details

Defined in Pantry.Types

Associated Types

type Rep PackageLocationImmutable 
Instance details

Defined in Pantry.Types

type Rep PackageLocationImmutable = D1 ('MetaData "PackageLocationImmutable" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" 'False) (C1 ('MetaCons "PLIHackage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PackageIdentifier) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlobKey) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TreeKey))) :+: (C1 ('MetaCons "PLIArchive" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Archive) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PackageMetadata)) :+: C1 ('MetaCons "PLIRepo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Repo) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PackageMetadata))))
Show PackageLocationImmutable 
Instance details

Defined in Pantry.Types

NFData PackageLocationImmutable 
Instance details

Defined in Pantry.Types

Eq PackageLocationImmutable 
Instance details

Defined in Pantry.Types

Ord PackageLocationImmutable 
Instance details

Defined in Pantry.Types

Display PackageLocationImmutable 
Instance details

Defined in Pantry.Types

FromJSON (WithJSONWarnings (Unresolved PackageLocationImmutable)) 
Instance details

Defined in Pantry.Types

type Rep PackageLocationImmutable 
Instance details

Defined in Pantry.Types

type Rep PackageLocationImmutable = D1 ('MetaData "PackageLocationImmutable" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" 'False) (C1 ('MetaCons "PLIHackage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PackageIdentifier) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlobKey) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TreeKey))) :+: (C1 ('MetaCons "PLIArchive" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Archive) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PackageMetadata)) :+: C1 ('MetaCons "PLIRepo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Repo) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PackageMetadata))))

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

RSLSynonym !SnapName

Snapshot synonym (LTS/Nightly).

Since: 0.5.0.0

Instances

Instances details
ToJSON RawSnapshotLocation 
Instance details

Defined in Pantry.Types

Generic RawSnapshotLocation 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RawSnapshotLocation 
Instance details

Defined in Pantry.Types

type Rep RawSnapshotLocation = D1 ('MetaData "RawSnapshotLocation" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" 'False) ((C1 ('MetaCons "RSLCompiler" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WantedCompiler)) :+: C1 ('MetaCons "RSLUrl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe BlobKey)))) :+: (C1 ('MetaCons "RSLFilePath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ResolvedPath File))) :+: C1 ('MetaCons "RSLSynonym" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SnapName))))
Show RawSnapshotLocation 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> RawSnapshotLocation -> ShowS

show :: RawSnapshotLocation -> String

showList :: [RawSnapshotLocation] -> ShowS

NFData RawSnapshotLocation 
Instance details

Defined in Pantry.Types

Methods

rnf :: RawSnapshotLocation -> ()

Eq RawSnapshotLocation 
Instance details

Defined in Pantry.Types

Ord RawSnapshotLocation 
Instance details

Defined in Pantry.Types

Display RawSnapshotLocation 
Instance details

Defined in Pantry.Types

Methods

display :: RawSnapshotLocation -> Utf8Builder

textDisplay :: RawSnapshotLocation -> Text

Pretty RawSnapshotLocation 
Instance details

Defined in Pantry.Types

Methods

pretty :: RawSnapshotLocation -> StyleDoc

FromJSON (WithJSONWarnings (Unresolved RawSnapshotLocation)) 
Instance details

Defined in Pantry.Types

type Rep RawSnapshotLocation 
Instance details

Defined in Pantry.Types

type Rep RawSnapshotLocation = D1 ('MetaData "RawSnapshotLocation" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" 'False) ((C1 ('MetaCons "RSLCompiler" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WantedCompiler)) :+: C1 ('MetaCons "RSLUrl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe BlobKey)))) :+: (C1 ('MetaCons "RSLFilePath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ResolvedPath File))) :+: C1 ('MetaCons "RSLSynonym" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SnapName))))

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

Defined in Pantry.Types

Generic SnapshotLocation 
Instance details

Defined in Pantry.Types

Associated Types

type Rep SnapshotLocation 
Instance details

Defined in Pantry.Types

type Rep SnapshotLocation = D1 ('MetaData "SnapshotLocation" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" 'False) (C1 ('MetaCons "SLCompiler" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WantedCompiler)) :+: (C1 ('MetaCons "SLUrl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlobKey)) :+: C1 ('MetaCons "SLFilePath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ResolvedPath File)))))
Show SnapshotLocation 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> SnapshotLocation -> ShowS

show :: SnapshotLocation -> String

showList :: [SnapshotLocation] -> ShowS

NFData SnapshotLocation 
Instance details

Defined in Pantry.Types

Methods

rnf :: SnapshotLocation -> ()

Eq SnapshotLocation 
Instance details

Defined in Pantry.Types

Ord SnapshotLocation 
Instance details

Defined in Pantry.Types

Display SnapshotLocation 
Instance details

Defined in Pantry.Types

Methods

display :: SnapshotLocation -> Utf8Builder

textDisplay :: SnapshotLocation -> Text

FromJSON (WithJSONWarnings (Unresolved SnapshotLocation)) 
Instance details

Defined in Pantry.Types

type Rep SnapshotLocation 
Instance details

Defined in Pantry.Types

type Rep SnapshotLocation = D1 ('MetaData "SnapshotLocation" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" 'False) (C1 ('MetaCons "SLCompiler" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WantedCompiler)) :+: (C1 ('MetaCons "SLUrl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlobKey)) :+: C1 ('MetaCons "SLFilePath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ResolvedPath File)))))

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

Instances

Instances details
Show SnapshotPackage 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> SnapshotPackage -> ShowS

show :: SnapshotPackage -> String

showList :: [SnapshotPackage] -> ShowS

data RawSnapshotLayer Source #

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

Since: 0.1.0.0

Constructors

RawSnapshotLayer 

Fields

Instances

Instances details
ToJSON RawSnapshotLayer 
Instance details

Defined in Pantry.Types

Generic RawSnapshotLayer 
Instance details

Defined in Pantry.Types

Associated Types

type Rep RawSnapshotLayer 
Instance details

Defined in Pantry.Types

type Rep RawSnapshotLayer = D1 ('MetaData "RawSnapshotLayer" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" 'False) (C1 ('MetaCons "RawSnapshotLayer" 'PrefixI 'True) (((S1 ('MetaSel ('Just "rslParent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RawSnapshotLocation) :*: S1 ('MetaSel ('Just "rslCompiler") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe WantedCompiler))) :*: (S1 ('MetaSel ('Just "rslLocations") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [RawPackageLocationImmutable]) :*: S1 ('MetaSel ('Just "rslDropPackages") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set PackageName)))) :*: ((S1 ('MetaSel ('Just "rslFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map PackageName (Map FlagName Bool))) :*: S1 ('MetaSel ('Just "rslHidden") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map PackageName Bool))) :*: (S1 ('MetaSel ('Just "rslGhcOptions") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map PackageName [Text])) :*: S1 ('MetaSel ('Just "rslPublishTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime))))))
Show RawSnapshotLayer 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> RawSnapshotLayer -> ShowS

show :: RawSnapshotLayer -> String

showList :: [RawSnapshotLayer] -> ShowS

NFData RawSnapshotLayer 
Instance details

Defined in Pantry.Types

Methods

rnf :: RawSnapshotLayer -> ()

Eq RawSnapshotLayer 
Instance details

Defined in Pantry.Types

FromJSON (WithJSONWarnings (Unresolved RawSnapshotLayer)) 
Instance details

Defined in Pantry.Types

type Rep RawSnapshotLayer 
Instance details

Defined in Pantry.Types

type Rep RawSnapshotLayer = D1 ('MetaData "RawSnapshotLayer" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" 'False) (C1 ('MetaCons "RawSnapshotLayer" 'PrefixI 'True) (((S1 ('MetaSel ('Just "rslParent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RawSnapshotLocation) :*: S1 ('MetaSel ('Just "rslCompiler") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe WantedCompiler))) :*: (S1 ('MetaSel ('Just "rslLocations") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [RawPackageLocationImmutable]) :*: S1 ('MetaSel ('Just "rslDropPackages") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set PackageName)))) :*: ((S1 ('MetaSel ('Just "rslFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map PackageName (Map FlagName Bool))) :*: S1 ('MetaSel ('Just "rslHidden") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map PackageName Bool))) :*: (S1 ('MetaSel ('Just "rslGhcOptions") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map PackageName [Text])) :*: S1 ('MetaSel ('Just "rslPublishTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime))))))

data SnapshotLayer Source #

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

Since: 0.1.0.0

Constructors

SnapshotLayer 

Fields

  • slParent :: !SnapshotLocation

    The sl to extend from. This is either a specific compiler, or a SnapshotLocation which gives us more information (like packages). Ultimately, we'll end up with a CompilerVersion.

    Since: 0.1.0.0

  • slCompiler :: !(Maybe WantedCompiler)

    Override the compiler specified in slParent. Must be Nothing if using SLCompiler.

    Since: 0.1.0.0

  • slLocations :: ![PackageLocationImmutable]

    Where to grab all of the packages from.

    Since: 0.1.0.0

  • slDropPackages :: !(Set PackageName)

    Packages present in the parent which should not be included here.

    Since: 0.1.0.0

  • slFlags :: !(Map PackageName (Map FlagName Bool))

    Flag values to override from the defaults

    Since: 0.1.0.0

  • slHidden :: !(Map PackageName Bool)

    Packages which should be hidden when registering. This will affect, for example, the import parser in the script command. We use a Map instead of just a Set to allow overriding the hidden settings in a parent sl.

    Since: 0.1.0.0

  • slGhcOptions :: !(Map PackageName [Text])

    GHC options per package

    Since: 0.1.0.0

  • slPublishTime :: !(Maybe UTCTime)

    Publication timestamp for this snapshot. This field is optional, and is for informational purposes only.

    Since: 0.1.0.0

Instances

Instances details
ToJSON SnapshotLayer 
Instance details

Defined in Pantry.Types

Generic SnapshotLayer 
Instance details

Defined in Pantry.Types

Associated Types

type Rep SnapshotLayer 
Instance details

Defined in Pantry.Types

type Rep SnapshotLayer = D1 ('MetaData "SnapshotLayer" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" 'False) (C1 ('MetaCons "SnapshotLayer" 'PrefixI 'True) (((S1 ('MetaSel ('Just "slParent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SnapshotLocation) :*: S1 ('MetaSel ('Just "slCompiler") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe WantedCompiler))) :*: (S1 ('MetaSel ('Just "slLocations") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [PackageLocationImmutable]) :*: S1 ('MetaSel ('Just "slDropPackages") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set PackageName)))) :*: ((S1 ('MetaSel ('Just "slFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map PackageName (Map FlagName Bool))) :*: S1 ('MetaSel ('Just "slHidden") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map PackageName Bool))) :*: (S1 ('MetaSel ('Just "slGhcOptions") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map PackageName [Text])) :*: S1 ('MetaSel ('Just "slPublishTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime))))))
Show SnapshotLayer 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> SnapshotLayer -> ShowS

show :: SnapshotLayer -> String

showList :: [SnapshotLayer] -> ShowS

Eq SnapshotLayer 
Instance details

Defined in Pantry.Types

type Rep SnapshotLayer 
Instance details

Defined in Pantry.Types

type Rep SnapshotLayer = D1 ('MetaData "SnapshotLayer" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" 'False) (C1 ('MetaCons "SnapshotLayer" 'PrefixI 'True) (((S1 ('MetaSel ('Just "slParent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SnapshotLocation) :*: S1 ('MetaSel ('Just "slCompiler") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe WantedCompiler))) :*: (S1 ('MetaSel ('Just "slLocations") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [PackageLocationImmutable]) :*: S1 ('MetaSel ('Just "slDropPackages") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set PackageName)))) :*: ((S1 ('MetaSel ('Just "slFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map PackageName (Map FlagName Bool))) :*: S1 ('MetaSel ('Just "slHidden") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map PackageName Bool))) :*: (S1 ('MetaSel ('Just "slGhcOptions") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map PackageName [Text])) :*: S1 ('MetaSel ('Just "slPublishTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime))))))

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

Instances details
FromJSON WantedCompiler 
Instance details

Defined in Pantry.Types

FromJSONKey WantedCompiler 
Instance details

Defined in Pantry.Types

Methods

fromJSONKey :: FromJSONKeyFunction WantedCompiler

fromJSONKeyList :: FromJSONKeyFunction [WantedCompiler]

ToJSON WantedCompiler 
Instance details

Defined in Pantry.Types

Generic WantedCompiler 
Instance details

Defined in Pantry.Types

Associated Types

type Rep WantedCompiler 
Instance details

Defined in Pantry.Types

type Rep WantedCompiler = D1 ('MetaData "WantedCompiler" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" 'False) (C1 ('MetaCons "WCGhc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Version)) :+: (C1 ('MetaCons "WCGhcGit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "WCGhcjs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Version) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Version))))
Show WantedCompiler 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> WantedCompiler -> ShowS

show :: WantedCompiler -> String

showList :: [WantedCompiler] -> ShowS

NFData WantedCompiler 
Instance details

Defined in Pantry.Types

Methods

rnf :: WantedCompiler -> ()

Eq WantedCompiler 
Instance details

Defined in Pantry.Types

Ord WantedCompiler 
Instance details

Defined in Pantry.Types

Display WantedCompiler 
Instance details

Defined in Pantry.Types

Methods

display :: WantedCompiler -> Utf8Builder

textDisplay :: WantedCompiler -> Text

type Rep WantedCompiler 
Instance details

Defined in Pantry.Types

type Rep WantedCompiler = D1 ('MetaData "WantedCompiler" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" 'False) (C1 ('MetaCons "WCGhc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Version)) :+: (C1 ('MetaCons "WCGhcGit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "WCGhcjs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Version) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Version))))

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

Defined in Pantry.Types

Methods

toJSON :: SnapName -> Value

toEncoding :: SnapName -> Encoding

toJSONList :: [SnapName] -> Value

toEncodingList :: [SnapName] -> Encoding

omitField :: SnapName -> Bool

Generic SnapName 
Instance details

Defined in Pantry.Types

Associated Types

type Rep SnapName 
Instance details

Defined in Pantry.Types

type Rep SnapName = D1 ('MetaData "SnapName" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" 'False) (C1 ('MetaCons "LTS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int)) :+: C1 ('MetaCons "Nightly" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Day)))

Methods

from :: SnapName -> Rep SnapName x

to :: Rep SnapName x -> SnapName

Show SnapName 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> SnapName -> ShowS

show :: SnapName -> String

showList :: [SnapName] -> ShowS

NFData SnapName 
Instance details

Defined in Pantry.Types

Methods

rnf :: SnapName -> ()

Eq SnapName 
Instance details

Defined in Pantry.Types

Methods

(==) :: SnapName -> SnapName -> Bool

(/=) :: SnapName -> SnapName -> Bool

Ord SnapName 
Instance details

Defined in Pantry.Types

Methods

compare :: SnapName -> SnapName -> Ordering

(<) :: SnapName -> SnapName -> Bool

(<=) :: SnapName -> SnapName -> Bool

(>) :: SnapName -> SnapName -> Bool

(>=) :: SnapName -> SnapName -> Bool

max :: SnapName -> SnapName -> SnapName

min :: SnapName -> SnapName -> SnapName

Display SnapName 
Instance details

Defined in Pantry.Types

Methods

display :: SnapName -> Utf8Builder

textDisplay :: SnapName -> Text

type Rep SnapName 
Instance details

Defined in Pantry.Types

type Rep SnapName = D1 ('MetaData "SnapName" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-internal" 'False) (C1 ('MetaCons "LTS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int)) :+: C1 ('MetaCons "Nightly" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Day)))

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

Get the location of a snapshot synonym from the PantryConfig.

Since: 0.5.0.0

Global hints

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

Defined in Pantry.Types

Generic GlobalHintsLocation 
Instance details

Defined in Pantry.Types

Associated Types

type Rep GlobalHintsLocation 
Instance details

Defined in Pantry.Types

type Rep GlobalHintsLocation = D1 ('MetaData "GlobalHintsLocation" "Pantry.Types" "pantry-0.10.0-IEfuNZUJgyXD7ssWSTK1cT-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))))
Show GlobalHintsLocation 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> GlobalHintsLocation -> ShowS

show :: GlobalHintsLocation -> String

showList :: [GlobalHintsLocation] -> ShowS

NFData GlobalHintsLocation 
Instance details

Defined in Pantry.Types

Methods

rnf :: GlobalHintsLocation -> ()

Eq GlobalHintsLocation 
Instance details

Defined in Pantry.Types

Ord GlobalHintsLocation 
Instance details

Defined in Pantry.Types

Display GlobalHintsLocation 
Instance details

Defined in Pantry.Types

Methods

display :: GlobalHintsLocation -> Utf8Builder

textDisplay :: GlobalHintsLocation -> Text

Pretty GlobalHintsLocation 
Instance details

Defined in Pantry.Types

Methods

pretty :: GlobalHintsLocation -> StyleDoc

FromJSON (WithJSONWarnings (Unresolved GlobalHintsLocation)) 
Instance details

Defined in Pantry.Types

type Rep GlobalHintsLocation 
Instance details

Defined in Pantry.Types

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

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

loadPackageRaw :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env Package Source #

Load a Package from a RawPackageLocationImmutable.

Load the package either from the local DB, Casa, or as a last resort, the third party (hackage, archive or repo).

Since: 0.1.0.0

tryLoadPackageRawViaCasa :: (HasLogFunc env, HasPantryConfig env, HasProcessContext env) => RawPackageLocationImmutable -> TreeKey -> RIO env (Maybe Package) Source #

Maybe load the package from Casa.

loadPackage :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => PackageLocationImmutable -> RIO env Package Source #

Load a Package from a PackageLocationImmutable.

Since: 0.1.0.0

loadRawSnapshotLayer :: (HasPantryConfig env, HasLogFunc env) => RawSnapshotLocation -> RIO env (Either WantedCompiler (RawSnapshotLayer, CompletedSL)) Source #

Parse a SnapshotLayer value from a SnapshotLocation.

Returns a Left value if provided an SLCompiler constructor. Otherwise, returns a Right value providing both the Snapshot and a hash of the input configuration file.

Since: 0.1.0.0

loadSnapshotLayer :: (HasPantryConfig env, HasLogFunc env) => SnapshotLocation -> RIO env (Either WantedCompiler RawSnapshotLayer) Source #

Parse a SnapshotLayer value from a SnapshotLocation.

Returns a Left value if provided an SLCompiler constructor. Otherwise, returns a Right value providing both the Snapshot and a hash of the input configuration file.

Since: 0.1.0.0

loadSnapshot :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => SnapshotLocation -> RIO env RawSnapshot Source #

Parse a RawSnapshot (all layers) from a SnapshotLocation.

Since: 0.1.0.0

loadAndCompleteSnapshot Source #

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. Debug output will include the raw snapshot layer.

Since: 0.1.0.0

loadAndCompleteSnapshot' Source #

Arguments

:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) 
=> Bool

Debug output includes the raw snapshot layer

-> SnapshotLocation 
-> Map RawSnapshotLocation SnapshotLocation

Cached snapshot locations from lock file

-> Map RawPackageLocationImmutable PackageLocationImmutable

Cached locations from lock file

-> RIO env (Snapshot, [CompletedSL], [CompletedPLI]) 

As for loadAndCompleteSnapshot but allows toggling of the debug output of the raw snapshot layer.

Since: 0.5.7

loadAndCompleteSnapshotRaw Source #

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. Debug output will include the raw snapshot layer.

Since: 0.1.0.0

loadAndCompleteSnapshotRaw' Source #

Arguments

:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) 
=> Bool

Debug output includes the raw snapshot layer

-> RawSnapshotLocation 
-> Map RawSnapshotLocation SnapshotLocation

Cached snapshot locations from lock file

-> Map RawPackageLocationImmutable PackageLocationImmutable

Cached locations from lock file

-> RIO env (Snapshot, [CompletedSL], [CompletedPLI]) 

As for loadAndCompleteSnapshotRaw but allows toggling of the debug output of the raw snapshot layer.

Since: 0.5.7

data CompletedSL Source #

A completed snapshot location, including the original raw and completed information.

Since: 0.1.0.0

data CompletedPLI Source #

A completed package location, including the original raw and completed information.

Since: 0.1.0.0

addPackagesToSnapshot Source #

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

Constructors

AddPackagesConfig 

Fields

Completion functions

data CompletePackageLocation Source #

Complete package location, plus whether the package has a cabal file. This is relevant to reproducibility, see https://tech.fpcomplete.com/blog/storing-generated-cabal-files

Since: 0.4.0.0

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

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

Since: 0.1.0.0

completeSnapshotLocation :: (HasPantryConfig env, HasLogFunc env) => RawSnapshotLocation -> RIO env SnapshotLocation Source #

Add in hashes to make a SnapshotLocation reproducible.

Since: 0.1.0.0

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

Warn if the package uses PCHpack.

Since: 0.4.0.0

Parsers

parseWantedCompiler :: Text -> Either PantryException WantedCompiler Source #

Parse a Text into a WantedCompiler value.

Since: 0.1.0.0

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

Parse the short representation of a SnapName.

Since: 0.5.0.0

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

Parse a hackage text.

Since: 0.1.0.0

Cabal values

parsePackageIdentifier :: String -> Maybe PackageIdentifier Source #

This is almost a copy of Cabal's parser for package identifiers, the main difference is in the fact that Stack requires version to be present while Cabal uses "null version" as a default value

Since: 0.1.0.0

parsePackageName :: String -> Maybe PackageName Source #

Parse a package name from a String.

Since: 0.1.0.0

parsePackageNameThrowing :: MonadThrow m => String -> m PackageName Source #

Parse a package name from a String throwing on failure

Since: 0.1.0.0

parseFlagName :: String -> Maybe FlagName Source #

Parse a flag name from a String.

Since: 0.1.0.0

parseVersion :: String -> Maybe Version Source #

Parse a version from a String.

Since: 0.1.0.0

parseVersionThrowing :: MonadThrow m => String -> m Version Source #

Parse a package version from a String throwing on failure

Since: 0.1.0.0

Cabal helpers

packageIdentifierString :: PackageIdentifier -> String Source #

Render a package identifier as a String.

Since: 0.1.0.0

packageNameString :: PackageName -> String Source #

Render a package name as a String.

Since: 0.1.0.0

flagNameString :: FlagName -> String Source #

Render a flag name as a String.

Since: 0.1.0.0

versionString :: Version -> String Source #

Render a version as a String.

Since: 0.1.0.0

moduleNameString :: ModuleName -> String Source #

Render a module name as a String.

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

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

Defined in Pantry.Types

Methods

parseJSON :: Value -> Parser (CabalString a)

parseJSONList :: Value -> Parser [CabalString a]

omittedField :: Maybe (CabalString a)

IsCabalString a => FromJSONKey (CabalString a) 
Instance details

Defined in Pantry.Types

Methods

fromJSONKey :: FromJSONKeyFunction (CabalString a)

fromJSONKeyList :: FromJSONKeyFunction [CabalString a]

Pretty a => ToJSON (CabalString a) 
Instance details

Defined in Pantry.Types

Methods

toJSON :: CabalString a -> Value

toEncoding :: CabalString a -> Encoding

toJSONList :: [CabalString a] -> Value

toEncodingList :: [CabalString a] -> Encoding

omitField :: CabalString a -> Bool

Pretty a => ToJSONKey (CabalString a) 
Instance details

Defined in Pantry.Types

Methods

toJSONKey :: ToJSONKeyFunction (CabalString a)

toJSONKeyList :: ToJSONKeyFunction [CabalString a]

Show a => Show (CabalString a) 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> CabalString a -> ShowS

show :: CabalString a -> String

showList :: [CabalString a] -> ShowS

Eq a => Eq (CabalString a) 
Instance details

Defined in Pantry.Types

Methods

(==) :: CabalString a -> CabalString a -> Bool

(/=) :: CabalString a -> CabalString a -> Bool

Ord a => Ord (CabalString a) 
Instance details

Defined in Pantry.Types

Methods

compare :: CabalString a -> CabalString a -> Ordering

(<) :: CabalString a -> CabalString a -> Bool

(<=) :: CabalString a -> CabalString a -> Bool

(>) :: CabalString a -> CabalString a -> Bool

(>=) :: CabalString a -> CabalString a -> Bool

max :: CabalString a -> CabalString a -> CabalString a

min :: CabalString a -> CabalString a -> CabalString a

toCabalStringMap :: Map a v -> Map (CabalString a) v Source #

Wrap the keys in a Map with a CabalString to get a ToJSON instance.

Since: 0.1.0.0

unCabalStringMap :: Map (CabalString a) v -> Map a v Source #

Unwrap the CabalString from the keys in a Map to use a FromJSON instance.

Since: 0.1.0.0

gpdPackageIdentifier :: GenericPackageDescription -> PackageIdentifier Source #

Get the PackageIdentifier from a GenericPackageDescription.

Since: 0.1.0.0

gpdPackageName :: GenericPackageDescription -> PackageName Source #

Get the PackageName from a GenericPackageDescription.

Since: 0.1.0.0

gpdVersion :: GenericPackageDescription -> Version Source #

Get the Version from a GenericPackageDescription.

Since: 0.1.0.0

Package location

fetchPackages :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env, Foldable f) => f PackageLocationImmutable -> RIO env () Source #

Download all of the packages provided into the local cache without performing any unpacking. Can be useful for build tools wanting to prefetch or provide an offline mode.

Since: 0.1.0.0

unpackPackageLocationRaw Source #

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

loadCabalFileRaw Source #

Arguments

:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) 
=> Maybe Text

The program name used by Hpack (the library), defaults to "hpack".

-> RawPackageLocation 
-> RIO env GenericPackageDescription 

Same as loadCabalFileRawImmutable, but takes a RawPackageLocation. Never prints warnings, see loadCabalFilePath for that.

Since: 0.8.0

loadCabalFile Source #

Arguments

:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) 
=> Maybe Text

The program name used by Hpack (the library), defaults to "hpack".

-> PackageLocation 
-> RIO env GenericPackageDescription 

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

Since: 0.8.0

loadCabalFileRawImmutable :: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) => RawPackageLocationImmutable -> RIO env GenericPackageDescription Source #

Load the cabal file for the given RawPackageLocationImmutable.

This function ignores all warnings.

Note that, for now, this will not allow support for hpack files in these package locations. Instead, all 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.

Since: 0.1.0.0

loadCabalFilePath Source #

Arguments

:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) 
=> Maybe Text

The program name used by Hpack (the library), defaults to "hpack".

-> Path Abs Dir

project directory, with a cabal file or hpack file

-> RIO env (PrintWarnings -> IO GenericPackageDescription, PackageName, Path Abs File) 

Parse the Cabal file for the package inside the given directory. Performs various sanity checks, such as the file name being correct and having only a single Cabal file.

Since: 0.8.0

findOrGenerateCabalFile Source #

Arguments

:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) 
=> Maybe Text

The program name used by Hpack (the library), defaults to "hpack".

-> Path Abs Dir

package directory

-> RIO env (PackageName, Path Abs File) 

Get the file name for the Cabal file in the given directory.

If no Cabal file is present, or more than one is present, an exception is thrown via throwM.

If the directory contains a file named package.yaml, Hpack is used to generate a Cabal file from it.

Since: 0.8.0

data PrintWarnings Source #

Should we print warnings when loading a cabal file?

Since: 0.1.0.0

Hackage index

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

Instances

Instances details
Show RequireHackageIndex Source # 
Instance details

Defined in Pantry.Hackage

Methods

showsPrec :: Int -> RequireHackageIndex -> ShowS

show :: RequireHackageIndex -> String

showList :: [RequireHackageIndex] -> ShowS

hackageIndexTarballL :: HasPantryConfig env => SimpleGetter env (Path Abs File) Source #

Where does pantry download its 01-index.tar file from Hackage?

Since: 0.1.0.0

getHackagePackageVersions Source #

Arguments

:: (HasPantryConfig env, HasLogFunc env) 
=> RequireHackageIndex 
-> UsePreferredVersions 
-> PackageName

package name

-> RIO env (Map Version (Map Revision BlobKey)) 

Returns the versions of the package available on Hackage.

Since: 0.1.0.0

getLatestHackageVersion Source #

Arguments

:: (HasPantryConfig env, HasLogFunc env) 
=> RequireHackageIndex 
-> PackageName

package name

-> UsePreferredVersions 
-> RIO env (Maybe PackageIdentifierRevision) 

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

Since: 0.1.0.0

getLatestHackageLocation Source #

Arguments

:: (HasPantryConfig env, HasLogFunc env, HasProcessContext env) 
=> RequireHackageIndex 
-> PackageName

package name

-> UsePreferredVersions 
-> RIO env (Maybe PackageLocationImmutable) 

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

Since: 0.1.0.0

getLatestHackageRevision Source #

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.

Since: 9.4.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

Instances

Instances details
Show SnapshotCacheHash 
Instance details

Defined in Pantry.Types

Methods

showsPrec :: Int -> SnapshotCacheHash -> ShowS

show :: SnapshotCacheHash -> String

showList :: [SnapshotCacheHash] -> ShowS

withSnapshotCache :: (HasPantryConfig env, HasLogFunc env) => SnapshotCacheHash -> RIO env (Map PackageName (Set ModuleName)) -> ((ModuleName -> RIO env [PackageName]) -> RIO env a) -> RIO env a Source #

Use a snapshot cache, which caches which modules are in which packages in a given snapshot. This is mostly intended for usage by Stack.

Since: 0.1.0.0