stack-1.6.3.1: The Haskell Tool Stack

Safe HaskellNone
LanguageHaskell2010

Stack.Types.BuildPlan

Contents

Description

Shared types for various stackage packages.

Synopsis

Types

data SnapshotDef Source #

A definition of a snapshot. This could be a Stackage snapshot or something custom. It does not include information on the global package database, this is added later.

It may seem more logic to attach flags, options, etc, directly with the desired package. However, this isn't possible yet: our definition may contain tarballs or Git repos, and we don't actually know the package names contained there. Therefore, we capture all of this additional information by package name, and later in the snapshot load step we will resolve the contents of tarballs and repos, figure out package names, and assigned values appropriately.

Constructors

SnapshotDef 

Fields

Instances

Eq SnapshotDef Source # 
Data SnapshotDef Source # 

Methods

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

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

toConstr :: SnapshotDef -> Constr #

dataTypeOf :: SnapshotDef -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SnapshotDef Source # 
Generic SnapshotDef Source # 

Associated Types

type Rep SnapshotDef :: * -> * #

NFData SnapshotDef Source # 

Methods

rnf :: SnapshotDef -> () #

Store SnapshotDef Source # 
type Rep SnapshotDef Source # 

sdRawPathName :: SnapshotDef -> String Source #

A relative file path including a unique string for the given snapshot.

data PackageLocation subdirs Source #

Where to get the contents of a package (including cabal file revisions) from.

A GADT may be more logical than the index parameter, but this plays more nicely with Generic deriving.

Constructors

PLFilePath !FilePath

Note that we use FilePath and not Paths. The goal is: first parse the value raw, and then use canonicalizePath and parseAbsDir.

PLArchive !(Archive subdirs) 
PLRepo !(Repo subdirs)

Stored in a source control repository

Instances

Functor PackageLocation Source # 

Methods

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

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

Eq subdirs => Eq (PackageLocation subdirs) Source # 

Methods

(==) :: PackageLocation subdirs -> PackageLocation subdirs -> Bool #

(/=) :: PackageLocation subdirs -> PackageLocation subdirs -> Bool #

Data subdirs => Data (PackageLocation subdirs) Source # 

Methods

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

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

toConstr :: PackageLocation subdirs -> Constr #

dataTypeOf :: PackageLocation subdirs -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord subdirs => Ord (PackageLocation subdirs) Source # 

Methods

compare :: PackageLocation subdirs -> PackageLocation subdirs -> Ordering #

(<) :: PackageLocation subdirs -> PackageLocation subdirs -> Bool #

(<=) :: PackageLocation subdirs -> PackageLocation subdirs -> Bool #

(>) :: PackageLocation subdirs -> PackageLocation subdirs -> Bool #

(>=) :: PackageLocation subdirs -> PackageLocation subdirs -> Bool #

max :: PackageLocation subdirs -> PackageLocation subdirs -> PackageLocation subdirs #

min :: PackageLocation subdirs -> PackageLocation subdirs -> PackageLocation subdirs #

Show subdirs => Show (PackageLocation subdirs) Source # 

Methods

showsPrec :: Int -> PackageLocation subdirs -> ShowS #

show :: PackageLocation subdirs -> String #

showList :: [PackageLocation subdirs] -> ShowS #

Generic (PackageLocation subdirs) Source # 

Associated Types

type Rep (PackageLocation subdirs) :: * -> * #

Methods

from :: PackageLocation subdirs -> Rep (PackageLocation subdirs) x #

to :: Rep (PackageLocation subdirs) x -> PackageLocation subdirs #

NFData a => NFData (PackageLocation a) Source # 

Methods

rnf :: PackageLocation a -> () #

(~) * subdirs Subdirs => ToJSON (PackageLocation subdirs) Source # 
(~) * subdirs Subdirs => FromJSON (WithJSONWarnings (PackageLocation subdirs)) Source # 
Store a => Store (PackageLocation a) Source # 
type Rep (PackageLocation subdirs) Source # 
type Rep (PackageLocation subdirs) = D1 * (MetaData "PackageLocation" "Stack.Types.BuildPlan" "stack-1.6.3.1-Lx3ZSkZ5nhFFvhJafO580B" False) ((:+:) * (C1 * (MetaCons "PLFilePath" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * FilePath))) ((:+:) * (C1 * (MetaCons "PLArchive" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Archive subdirs)))) (C1 * (MetaCons "PLRepo" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Repo subdirs))))))

data PackageLocationIndex subdirs Source #

Add in the possibility of getting packages from the index (including cabal file revisions). We have special handling of this case in many places in the codebase, and therefore represent it with a separate data type from PackageLocation.

Constructors

PLIndex !PackageIdentifierRevision

Grab the package from the package index with the given version and (optional) cabal file info to specify the correct revision.

PLOther !(PackageLocation subdirs) 

Instances

Functor PackageLocationIndex Source # 
Eq subdirs => Eq (PackageLocationIndex subdirs) Source # 
Data subdirs => Data (PackageLocationIndex subdirs) Source # 

Methods

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

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

toConstr :: PackageLocationIndex subdirs -> Constr #

dataTypeOf :: PackageLocationIndex subdirs -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord subdirs => Ord (PackageLocationIndex subdirs) Source # 
Show subdirs => Show (PackageLocationIndex subdirs) Source # 
Generic (PackageLocationIndex subdirs) Source # 

Associated Types

type Rep (PackageLocationIndex subdirs) :: * -> * #

Methods

from :: PackageLocationIndex subdirs -> Rep (PackageLocationIndex subdirs) x #

to :: Rep (PackageLocationIndex subdirs) x -> PackageLocationIndex subdirs #

NFData a => NFData (PackageLocationIndex a) Source # 

Methods

rnf :: PackageLocationIndex a -> () #

(~) * subdirs Subdirs => ToJSON (PackageLocationIndex subdirs) Source # 
(~) * subdirs Subdirs => FromJSON (WithJSONWarnings (PackageLocationIndex subdirs)) Source # 
Store a => Store (PackageLocationIndex a) Source # 
type Rep (PackageLocationIndex subdirs) Source # 
type Rep (PackageLocationIndex subdirs) = D1 * (MetaData "PackageLocationIndex" "Stack.Types.BuildPlan" "stack-1.6.3.1-Lx3ZSkZ5nhFFvhJafO580B" False) ((:+:) * (C1 * (MetaCons "PLIndex" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * PackageIdentifierRevision))) (C1 * (MetaCons "PLOther" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (PackageLocation subdirs)))))

data RepoType Source #

The type of a source control repository.

Constructors

RepoGit 
RepoHg 

Instances

Eq RepoType Source # 
Data RepoType Source # 

Methods

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

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

toConstr :: RepoType -> Constr #

dataTypeOf :: RepoType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RepoType Source # 
Show RepoType Source # 
Generic RepoType Source # 

Associated Types

type Rep RepoType :: * -> * #

Methods

from :: RepoType -> Rep RepoType x #

to :: Rep RepoType x -> RepoType #

NFData RepoType Source # 

Methods

rnf :: RepoType -> () #

Store RepoType Source # 
type Rep RepoType Source # 
type Rep RepoType = D1 * (MetaData "RepoType" "Stack.Types.BuildPlan" "stack-1.6.3.1-Lx3ZSkZ5nhFFvhJafO580B" False) ((:+:) * (C1 * (MetaCons "RepoGit" PrefixI False) (U1 *)) (C1 * (MetaCons "RepoHg" PrefixI False) (U1 *)))

data Subdirs Source #

Instances

Eq Subdirs Source # 

Methods

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

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

Data Subdirs Source # 

Methods

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

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

toConstr :: Subdirs -> Constr #

dataTypeOf :: Subdirs -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Subdirs Source # 
Generic Subdirs Source # 

Associated Types

type Rep Subdirs :: * -> * #

Methods

from :: Subdirs -> Rep Subdirs x #

to :: Rep Subdirs x -> Subdirs #

NFData Subdirs Source # 

Methods

rnf :: Subdirs -> () #

FromJSON Subdirs Source # 
Store Subdirs Source # 
type Rep Subdirs Source # 
type Rep Subdirs = D1 * (MetaData "Subdirs" "Stack.Types.BuildPlan" "stack-1.6.3.1-Lx3ZSkZ5nhFFvhJafO580B" False) ((:+:) * (C1 * (MetaCons "DefaultSubdirs" PrefixI False) (U1 *)) (C1 * (MetaCons "ExplicitSubdirs" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [FilePath]))))

data Repo subdirs Source #

Information on packages stored in a source control repository.

Constructors

Repo 

Fields

Instances

Functor Repo Source # 

Methods

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

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

Eq subdirs => Eq (Repo subdirs) Source # 

Methods

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

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

Data subdirs => Data (Repo subdirs) Source # 

Methods

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

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

toConstr :: Repo subdirs -> Constr #

dataTypeOf :: Repo subdirs -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord subdirs => Ord (Repo subdirs) Source # 

Methods

compare :: Repo subdirs -> Repo subdirs -> Ordering #

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

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

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

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

max :: Repo subdirs -> Repo subdirs -> Repo subdirs #

min :: Repo subdirs -> Repo subdirs -> Repo subdirs #

Show subdirs => Show (Repo subdirs) Source # 

Methods

showsPrec :: Int -> Repo subdirs -> ShowS #

show :: Repo subdirs -> String #

showList :: [Repo subdirs] -> ShowS #

Generic (Repo subdirs) Source # 

Associated Types

type Rep (Repo subdirs) :: * -> * #

Methods

from :: Repo subdirs -> Rep (Repo subdirs) x #

to :: Rep (Repo subdirs) x -> Repo subdirs #

NFData a => NFData (Repo a) Source # 

Methods

rnf :: Repo a -> () #

Store a => Store (Repo a) Source # 

Methods

size :: Size (Repo a) #

poke :: Repo a -> Poke () #

peek :: Peek (Repo a) #

type Rep (Repo subdirs) Source # 
type Rep (Repo subdirs) = D1 * (MetaData "Repo" "Stack.Types.BuildPlan" "stack-1.6.3.1-Lx3ZSkZ5nhFFvhJafO580B" False) (C1 * (MetaCons "Repo" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "repoUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "repoCommit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "repoType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * RepoType)) (S1 * (MetaSel (Just Symbol "repoSubdirs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * subdirs)))))

data Archive subdirs 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.

Constructors

Archive 

Instances

Functor Archive Source # 

Methods

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

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

Eq subdirs => Eq (Archive subdirs) Source # 

Methods

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

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

Data subdirs => Data (Archive subdirs) Source # 

Methods

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

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

toConstr :: Archive subdirs -> Constr #

dataTypeOf :: Archive subdirs -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord subdirs => Ord (Archive subdirs) Source # 

Methods

compare :: Archive subdirs -> Archive subdirs -> Ordering #

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

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

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

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

max :: Archive subdirs -> Archive subdirs -> Archive subdirs #

min :: Archive subdirs -> Archive subdirs -> Archive subdirs #

Show subdirs => Show (Archive subdirs) Source # 

Methods

showsPrec :: Int -> Archive subdirs -> ShowS #

show :: Archive subdirs -> String #

showList :: [Archive subdirs] -> ShowS #

Generic (Archive subdirs) Source # 

Associated Types

type Rep (Archive subdirs) :: * -> * #

Methods

from :: Archive subdirs -> Rep (Archive subdirs) x #

to :: Rep (Archive subdirs) x -> Archive subdirs #

NFData a => NFData (Archive a) Source # 

Methods

rnf :: Archive a -> () #

Store a => Store (Archive a) Source # 

Methods

size :: Size (Archive a) #

poke :: Archive a -> Poke () #

peek :: Peek (Archive a) #

type Rep (Archive subdirs) Source # 
type Rep (Archive subdirs) = D1 * (MetaData "Archive" "Stack.Types.BuildPlan" "stack-1.6.3.1-Lx3ZSkZ5nhFFvhJafO580B" False) (C1 * (MetaCons "Archive" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "archiveUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "archiveSubdirs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * subdirs)) (S1 * (MetaSel (Just Symbol "archiveHash") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe StaticSHA256))))))

newtype ExeName Source #

Name of an executable.

Constructors

ExeName 

Fields

Instances

Eq ExeName Source # 

Methods

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

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

Data ExeName Source # 

Methods

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

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

toConstr :: ExeName -> Constr #

dataTypeOf :: ExeName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ExeName Source # 
Show ExeName Source # 
IsString ExeName Source # 

Methods

fromString :: String -> ExeName #

Generic ExeName Source # 

Associated Types

type Rep ExeName :: * -> * #

Methods

from :: ExeName -> Rep ExeName x #

to :: Rep ExeName x -> ExeName #

NFData ExeName Source # 

Methods

rnf :: ExeName -> () #

Hashable ExeName Source # 

Methods

hashWithSalt :: Int -> ExeName -> Int #

hash :: ExeName -> Int #

Store ExeName Source # 
type Rep ExeName Source # 
type Rep ExeName = D1 * (MetaData "ExeName" "Stack.Types.BuildPlan" "stack-1.6.3.1-Lx3ZSkZ5nhFFvhJafO580B" True) (C1 * (MetaCons "ExeName" PrefixI True) (S1 * (MetaSel (Just Symbol "unExeName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

data LoadedSnapshot Source #

A fully loaded snapshot combined , including information gleaned from the global database and parsing cabal files.

Invariant: a global package may not depend upon a snapshot package, a snapshot may not depend upon a local or project, and all dependencies must be satisfied.

Instances

Eq LoadedSnapshot Source # 
Data LoadedSnapshot Source # 

Methods

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

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

toConstr :: LoadedSnapshot -> Constr #

dataTypeOf :: LoadedSnapshot -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LoadedSnapshot Source # 
Generic LoadedSnapshot Source # 

Associated Types

type Rep LoadedSnapshot :: * -> * #

NFData LoadedSnapshot Source # 

Methods

rnf :: LoadedSnapshot -> () #

Store LoadedSnapshot Source # 
type Rep LoadedSnapshot Source # 

data LoadedPackageInfo loc Source #

Information on a single package for the LoadedSnapshot which can be installed.

Note that much of the information below (such as the package dependencies or exposed modules) can be conditional in the cabal file, which means it will vary based on flags, arch, and OS.

Constructors

LoadedPackageInfo 

Fields

  • lpiVersion :: !Version

    This must match the version specified within rpiDef.

  • lpiLocation :: !loc

    Where to get the package from. This could be a few different things:

    • For a global package, it will be the GhcPkgId. (If we end up needing to rebuild this because we've changed a dependency, we will take it from the package index with no CabalFileInfo.
    • For a dependency, it will be a PackageLocation.
    • For a project package, it will be a Path Abs Dir.
  • lpiFlags :: !(Map FlagName Bool)

    Flags to build this package with.

  • lpiGhcOptions :: ![Text]

    GHC options to use when building this package.

  • lpiPackageDeps :: !(Map PackageName VersionIntervals)

    All packages which must be builtcopiedregistered before this package.

  • lpiProvidedExes :: !(Set ExeName)

    The names of executables provided by this package, for performing build tool lookups.

  • lpiNeededExes :: !(Map ExeName VersionIntervals)

    Executables needed by this package.

  • lpiExposedModules :: !(Set ModuleName)

    Modules exposed by this package's library

  • lpiHide :: !Bool

    Should this package be hidden in the database. Affects the script interpreter's module name import parser.

Instances

Functor LoadedPackageInfo Source # 
Eq loc => Eq (LoadedPackageInfo loc) Source # 
Data loc => Data (LoadedPackageInfo loc) Source # 

Methods

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

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

toConstr :: LoadedPackageInfo loc -> Constr #

dataTypeOf :: LoadedPackageInfo loc -> DataType #

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

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

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

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

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

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

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

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

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

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

Show loc => Show (LoadedPackageInfo loc) Source # 
Generic (LoadedPackageInfo loc) Source # 

Associated Types

type Rep (LoadedPackageInfo loc) :: * -> * #

NFData a => NFData (LoadedPackageInfo a) Source # 

Methods

rnf :: LoadedPackageInfo a -> () #

Store a => Store (LoadedPackageInfo a) Source # 
type Rep (LoadedPackageInfo loc) Source # 

newtype ModuleName Source #

Constructors

ModuleName 

Instances

Eq ModuleName Source # 
Data ModuleName Source # 

Methods

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

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

toConstr :: ModuleName -> Constr #

dataTypeOf :: ModuleName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ModuleName Source # 
Show ModuleName Source # 
Generic ModuleName Source # 

Associated Types

type Rep ModuleName :: * -> * #

NFData ModuleName Source # 

Methods

rnf :: ModuleName -> () #

Store ModuleName Source # 
type Rep ModuleName Source # 
type Rep ModuleName = D1 * (MetaData "ModuleName" "Stack.Types.BuildPlan" "stack-1.6.3.1-Lx3ZSkZ5nhFFvhJafO580B" True) (C1 * (MetaCons "ModuleName" PrefixI True) (S1 * (MetaSel (Just Symbol "unModuleName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ByteString)))

newtype ModuleInfo Source #

Constructors

ModuleInfo 

Instances

Eq ModuleInfo Source # 
Data ModuleInfo Source # 

Methods

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

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

toConstr :: ModuleInfo -> Constr #

dataTypeOf :: ModuleInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ModuleInfo Source # 
Show ModuleInfo Source # 
Generic ModuleInfo Source # 

Associated Types

type Rep ModuleInfo :: * -> * #

Monoid ModuleInfo Source # 
NFData ModuleInfo Source # 

Methods

rnf :: ModuleInfo -> () #

Store ModuleInfo Source # 
type Rep ModuleInfo Source # 
type Rep ModuleInfo = D1 * (MetaData "ModuleInfo" "Stack.Types.BuildPlan" "stack-1.6.3.1-Lx3ZSkZ5nhFFvhJafO580B" True) (C1 * (MetaCons "ModuleInfo" PrefixI True) (S1 * (MetaSel (Just Symbol "miModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Map ModuleName (Set PackageName)))))

setCompilerVersion :: CompilerVersion CVWanted -> SnapshotDef -> SnapshotDef Source #

Modify the wanted compiler version in this snapshot. This is used when overriding via the compiler value in a custom snapshot or stack.yaml file. We do _not_ need to modify the snapshot's hash for this: all binary caches of a snapshot are stored in a filepath that encodes the actual compiler version in addition to the hash. Therefore, modifications here will not lead to any invalid data.

sdWantedCompilerVersion :: SnapshotDef -> CompilerVersion CVWanted Source #

Determined the desired compiler version for this SnapshotDef.