stack-1.9.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 # 
Instance details

Defined in Stack.Types.BuildPlan

Data SnapshotDef Source # 
Instance details

Defined in Stack.Types.BuildPlan

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

Defined in Stack.Types.BuildPlan

Generic SnapshotDef Source # 
Instance details

Defined in Stack.Types.BuildPlan

Associated Types

type Rep SnapshotDef :: Type -> Type #

NFData SnapshotDef Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

rnf :: SnapshotDef -> () #

Store SnapshotDef Source # 
Instance details

Defined in Stack.Types.BuildPlan

type Rep SnapshotDef Source # 
Instance details

Defined in Stack.Types.BuildPlan

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

Defined in Stack.Types.BuildPlan

Methods

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

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

Eq subdirs => Eq (PackageLocation subdirs) Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

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

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

Data subdirs => Data (PackageLocation subdirs) Source # 
Instance details

Defined in Stack.Types.BuildPlan

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

Defined in Stack.Types.BuildPlan

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

Defined in Stack.Types.BuildPlan

Methods

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

show :: PackageLocation subdirs -> String #

showList :: [PackageLocation subdirs] -> ShowS #

Generic (PackageLocation subdirs) Source # 
Instance details

Defined in Stack.Types.BuildPlan

Associated Types

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

Methods

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

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

NFData a => NFData (PackageLocation a) Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

rnf :: PackageLocation a -> () #

subdirs ~ Subdirs => ToJSON (PackageLocation subdirs) Source # 
Instance details

Defined in Stack.Types.BuildPlan

subdirs ~ Subdirs => FromJSON (WithJSONWarnings (PackageLocation subdirs)) Source # 
Instance details

Defined in Stack.Types.BuildPlan

Store a => Store (PackageLocation a) Source # 
Instance details

Defined in Stack.Types.BuildPlan

type Rep (PackageLocation subdirs) Source # 
Instance details

Defined in Stack.Types.BuildPlan

type Rep (PackageLocation subdirs) = D1 (MetaData "PackageLocation" "Stack.Types.BuildPlan" "stack-1.9.3.1-Cy1tv1B2VcB4E3bvhLgbqY" False) (C1 (MetaCons "PLFilePath" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilePath)) :+: (C1 (MetaCons "PLArchive" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Archive subdirs))) :+: C1 (MetaCons "PLRepo" PrefixI False) (S1 (MetaSel (Nothing :: Maybe 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 # 
Instance details

Defined in Stack.Types.BuildPlan

Eq subdirs => Eq (PackageLocationIndex subdirs) Source # 
Instance details

Defined in Stack.Types.BuildPlan

Data subdirs => Data (PackageLocationIndex subdirs) Source # 
Instance details

Defined in Stack.Types.BuildPlan

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

Defined in Stack.Types.BuildPlan

Show subdirs => Show (PackageLocationIndex subdirs) Source # 
Instance details

Defined in Stack.Types.BuildPlan

Generic (PackageLocationIndex subdirs) Source # 
Instance details

Defined in Stack.Types.BuildPlan

Associated Types

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

Methods

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

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

NFData a => NFData (PackageLocationIndex a) Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

rnf :: PackageLocationIndex a -> () #

subdirs ~ Subdirs => ToJSON (PackageLocationIndex subdirs) Source # 
Instance details

Defined in Stack.Types.BuildPlan

subdirs ~ Subdirs => FromJSON (WithJSONWarnings (PackageLocationIndex subdirs)) Source # 
Instance details

Defined in Stack.Types.BuildPlan

Store a => Store (PackageLocationIndex a) Source # 
Instance details

Defined in Stack.Types.BuildPlan

type Rep (PackageLocationIndex subdirs) Source # 
Instance details

Defined in Stack.Types.BuildPlan

type Rep (PackageLocationIndex subdirs) = D1 (MetaData "PackageLocationIndex" "Stack.Types.BuildPlan" "stack-1.9.3.1-Cy1tv1B2VcB4E3bvhLgbqY" False) (C1 (MetaCons "PLIndex" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PackageIdentifierRevision)) :+: C1 (MetaCons "PLOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (PackageLocation subdirs))))

data RepoType Source #

The type of a source control repository.

Constructors

RepoGit 
RepoHg 
Instances
Eq RepoType Source # 
Instance details

Defined in Stack.Types.BuildPlan

Data RepoType Source # 
Instance details

Defined in Stack.Types.BuildPlan

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

Defined in Stack.Types.BuildPlan

Show RepoType Source # 
Instance details

Defined in Stack.Types.BuildPlan

Generic RepoType Source # 
Instance details

Defined in Stack.Types.BuildPlan

Associated Types

type Rep RepoType :: Type -> Type #

Methods

from :: RepoType -> Rep RepoType x #

to :: Rep RepoType x -> RepoType #

NFData RepoType Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

rnf :: RepoType -> () #

Store RepoType Source # 
Instance details

Defined in Stack.Types.BuildPlan

type Rep RepoType Source # 
Instance details

Defined in Stack.Types.BuildPlan

type Rep RepoType = D1 (MetaData "RepoType" "Stack.Types.BuildPlan" "stack-1.9.3.1-Cy1tv1B2VcB4E3bvhLgbqY" False) (C1 (MetaCons "RepoGit" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RepoHg" PrefixI False) (U1 :: Type -> Type))

data Subdirs Source #

Instances
Eq Subdirs Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

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

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

Data Subdirs Source # 
Instance details

Defined in Stack.Types.BuildPlan

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

Defined in Stack.Types.BuildPlan

Generic Subdirs Source # 
Instance details

Defined in Stack.Types.BuildPlan

Associated Types

type Rep Subdirs :: Type -> Type #

Methods

from :: Subdirs -> Rep Subdirs x #

to :: Rep Subdirs x -> Subdirs #

NFData Subdirs Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

rnf :: Subdirs -> () #

FromJSON Subdirs Source # 
Instance details

Defined in Stack.Types.BuildPlan

Store Subdirs Source # 
Instance details

Defined in Stack.Types.BuildPlan

type Rep Subdirs Source # 
Instance details

Defined in Stack.Types.BuildPlan

type Rep Subdirs = D1 (MetaData "Subdirs" "Stack.Types.BuildPlan" "stack-1.9.3.1-Cy1tv1B2VcB4E3bvhLgbqY" False) (C1 (MetaCons "DefaultSubdirs" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ExplicitSubdirs" PrefixI False) (S1 (MetaSel (Nothing :: Maybe 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 # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

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

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

Eq subdirs => Eq (Repo subdirs) Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

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

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

Data subdirs => Data (Repo subdirs) Source # 
Instance details

Defined in Stack.Types.BuildPlan

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

Defined in Stack.Types.BuildPlan

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

Defined in Stack.Types.BuildPlan

Methods

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

show :: Repo subdirs -> String #

showList :: [Repo subdirs] -> ShowS #

Generic (Repo subdirs) Source # 
Instance details

Defined in Stack.Types.BuildPlan

Associated Types

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

Methods

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

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

NFData a => NFData (Repo a) Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

rnf :: Repo a -> () #

Store a => Store (Repo a) Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

size :: Size (Repo a) #

poke :: Repo a -> Poke () #

peek :: Peek (Repo a) #

type Rep (Repo subdirs) Source # 
Instance details

Defined in Stack.Types.BuildPlan

type Rep (Repo subdirs) = D1 (MetaData "Repo" "Stack.Types.BuildPlan" "stack-1.9.3.1-Cy1tv1B2VcB4E3bvhLgbqY" 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 "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 # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

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

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

Eq subdirs => Eq (Archive subdirs) Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

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

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

Data subdirs => Data (Archive subdirs) Source # 
Instance details

Defined in Stack.Types.BuildPlan

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

Defined in Stack.Types.BuildPlan

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

Defined in Stack.Types.BuildPlan

Methods

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

show :: Archive subdirs -> String #

showList :: [Archive subdirs] -> ShowS #

Generic (Archive subdirs) Source # 
Instance details

Defined in Stack.Types.BuildPlan

Associated Types

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

Methods

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

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

NFData a => NFData (Archive a) Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

rnf :: Archive a -> () #

Store a => Store (Archive a) Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

size :: Size (Archive a) #

poke :: Archive a -> Poke () #

peek :: Peek (Archive a) #

type Rep (Archive subdirs) Source # 
Instance details

Defined in Stack.Types.BuildPlan

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

newtype ExeName Source #

Name of an executable.

Constructors

ExeName 

Fields

Instances
Eq ExeName Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

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

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

Data ExeName Source # 
Instance details

Defined in Stack.Types.BuildPlan

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

Defined in Stack.Types.BuildPlan

Show ExeName Source # 
Instance details

Defined in Stack.Types.BuildPlan

IsString ExeName Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

fromString :: String -> ExeName #

Generic ExeName Source # 
Instance details

Defined in Stack.Types.BuildPlan

Associated Types

type Rep ExeName :: Type -> Type #

Methods

from :: ExeName -> Rep ExeName x #

to :: Rep ExeName x -> ExeName #

NFData ExeName Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

rnf :: ExeName -> () #

Hashable ExeName Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

hashWithSalt :: Int -> ExeName -> Int #

hash :: ExeName -> Int #

Store ExeName Source # 
Instance details

Defined in Stack.Types.BuildPlan

type Rep ExeName Source # 
Instance details

Defined in Stack.Types.BuildPlan

type Rep ExeName = D1 (MetaData "ExeName" "Stack.Types.BuildPlan" "stack-1.9.3.1-Cy1tv1B2VcB4E3bvhLgbqY" True) (C1 (MetaCons "ExeName" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Stack.Types.BuildPlan

Data LoadedSnapshot Source # 
Instance details

Defined in Stack.Types.BuildPlan

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

Defined in Stack.Types.BuildPlan

Generic LoadedSnapshot Source # 
Instance details

Defined in Stack.Types.BuildPlan

Associated Types

type Rep LoadedSnapshot :: Type -> Type #

NFData LoadedSnapshot Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

rnf :: LoadedSnapshot -> () #

Store LoadedSnapshot Source # 
Instance details

Defined in Stack.Types.BuildPlan

type Rep LoadedSnapshot Source # 
Instance details

Defined in Stack.Types.BuildPlan

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.

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

Defined in Stack.Types.BuildPlan

Eq loc => Eq (LoadedPackageInfo loc) Source # 
Instance details

Defined in Stack.Types.BuildPlan

Data loc => Data (LoadedPackageInfo loc) Source # 
Instance details

Defined in Stack.Types.BuildPlan

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

Defined in Stack.Types.BuildPlan

Generic (LoadedPackageInfo loc) Source # 
Instance details

Defined in Stack.Types.BuildPlan

Associated Types

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

NFData a => NFData (LoadedPackageInfo a) Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

rnf :: LoadedPackageInfo a -> () #

Store a => Store (LoadedPackageInfo a) Source # 
Instance details

Defined in Stack.Types.BuildPlan

type Rep (LoadedPackageInfo loc) Source # 
Instance details

Defined in Stack.Types.BuildPlan

newtype ModuleName Source #

Constructors

ModuleName 
Instances
Eq ModuleName Source # 
Instance details

Defined in Stack.Types.BuildPlan

Data ModuleName Source # 
Instance details

Defined in Stack.Types.BuildPlan

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

Defined in Stack.Types.BuildPlan

Show ModuleName Source # 
Instance details

Defined in Stack.Types.BuildPlan

Generic ModuleName Source # 
Instance details

Defined in Stack.Types.BuildPlan

Associated Types

type Rep ModuleName :: Type -> Type #

NFData ModuleName Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

rnf :: ModuleName -> () #

Store ModuleName Source # 
Instance details

Defined in Stack.Types.BuildPlan

type Rep ModuleName Source # 
Instance details

Defined in Stack.Types.BuildPlan

type Rep ModuleName = D1 (MetaData "ModuleName" "Stack.Types.BuildPlan" "stack-1.9.3.1-Cy1tv1B2VcB4E3bvhLgbqY" True) (C1 (MetaCons "ModuleName" PrefixI True) (S1 (MetaSel (Just "unModuleName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

newtype ModuleInfo Source #

Constructors

ModuleInfo 
Instances
Eq ModuleInfo Source # 
Instance details

Defined in Stack.Types.BuildPlan

Data ModuleInfo Source # 
Instance details

Defined in Stack.Types.BuildPlan

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

Defined in Stack.Types.BuildPlan

Show ModuleInfo Source # 
Instance details

Defined in Stack.Types.BuildPlan

Generic ModuleInfo Source # 
Instance details

Defined in Stack.Types.BuildPlan

Associated Types

type Rep ModuleInfo :: Type -> Type #

Semigroup ModuleInfo Source # 
Instance details

Defined in Stack.Types.BuildPlan

Monoid ModuleInfo Source # 
Instance details

Defined in Stack.Types.BuildPlan

NFData ModuleInfo Source # 
Instance details

Defined in Stack.Types.BuildPlan

Methods

rnf :: ModuleInfo -> () #

Store ModuleInfo Source # 
Instance details

Defined in Stack.Types.BuildPlan

type Rep ModuleInfo Source # 
Instance details

Defined in Stack.Types.BuildPlan

type Rep ModuleInfo = D1 (MetaData "ModuleInfo" "Stack.Types.BuildPlan" "stack-1.9.3.1-Cy1tv1B2VcB4E3bvhLgbqY" True) (C1 (MetaCons "ModuleInfo" PrefixI True) (S1 (MetaSel (Just "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.