stack-1.5.1: The Haskell Tool Stack

Safe HaskellNone
LanguageHaskell2010

Stack.BuildPlan

Description

Resolving a build plan for a set of packages in a given Stackage snapshot.

Synopsis

Documentation

checkSnapBuildPlan :: (StackM env m, HasConfig env, HasGHCVariant env) => [GenericPackageDescription] -> Maybe (Map PackageName (Map FlagName Bool)) -> SnapName -> m BuildPlanCheck Source #

Check a set of GenericPackageDescriptions and a set of flags against a given snapshot. Returns how well the snapshot satisfies the dependencies of the packages.

data MiniBuildPlan Source #

A simplified version of the BuildPlan + cabal file.

Instances

Eq MiniBuildPlan Source # 
Data MiniBuildPlan Source # 

Methods

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

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

toConstr :: MiniBuildPlan -> Constr #

dataTypeOf :: MiniBuildPlan -> DataType #

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

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

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

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

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

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

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

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

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

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

Show MiniBuildPlan Source # 
Generic MiniBuildPlan Source # 

Associated Types

type Rep MiniBuildPlan :: * -> * #

NFData MiniBuildPlan Source # 

Methods

rnf :: MiniBuildPlan -> () #

Store MiniBuildPlan Source # 
type Rep MiniBuildPlan Source # 
type Rep MiniBuildPlan = D1 (MetaData "MiniBuildPlan" "Stack.Types.BuildPlan" "stack-1.5.1-5e9OdzxbAr7JlXF5YdN55t" False) (C1 (MetaCons "MiniBuildPlan" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "mbpCompilerVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 CompilerVersion)) (S1 (MetaSel (Just Symbol "mbpPackages") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Map PackageName MiniPackageInfo)))))

data MiniPackageInfo Source #

Information on a single package for the MiniBuildPlan.

Constructors

MiniPackageInfo 

Fields

Instances

Eq MiniPackageInfo Source # 
Data MiniPackageInfo Source # 

Methods

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

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

toConstr :: MiniPackageInfo -> Constr #

dataTypeOf :: MiniPackageInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Show MiniPackageInfo Source # 
Generic MiniPackageInfo Source # 
NFData MiniPackageInfo Source # 

Methods

rnf :: MiniPackageInfo -> () #

Store MiniPackageInfo Source # 
type Rep MiniPackageInfo Source # 

loadMiniBuildPlan :: (StackMiniM env m, HasConfig env, HasGHCVariant env) => SnapName -> m MiniBuildPlan Source #

Load up a MiniBuildPlan, preferably from cache

resolveBuildPlan Source #

Arguments

:: (StackMiniM env m, HasBuildConfig env) 
=> MiniBuildPlan 
-> (PackageName -> Bool)

is it shadowed by a local package?

-> Map PackageName (Set PackageName)

required packages, and users of it

-> m (Map PackageName (Version, Map FlagName Bool), Map PackageName (Set PackageName)) 

Determine the necessary packages to install to have the given set of packages available.

This function will not provide test suite and benchmark dependencies.

This may fail if a target package is not present in the BuildPlan.

selectBestSnapshot :: (StackM env m, HasConfig env, HasGHCVariant env) => [GenericPackageDescription] -> NonEmpty SnapName -> m (SnapName, BuildPlanCheck) Source #

Find a snapshot and set of flags that is compatible with and matches as best as possible with the given GenericPackageDescriptions.

getToolMap :: MiniBuildPlan -> Map Text (Set PackageName) Source #

Map from tool name to package providing it

shadowMiniBuildPlan :: MiniBuildPlan -> Set PackageName -> (MiniBuildPlan, Map PackageName MiniPackageInfo) Source #

Given a set of packages to shadow, this removes them, and any packages that transitively depend on them, from the MiniBuildPlan. The Map result yields all of the packages that were downstream of the shadowed packages. It does not include the shadowed packages.

showItems :: Show a => [a] -> Text Source #

parseCustomMiniBuildPlan Source #

Arguments

:: (StackMiniM env m, HasConfig env, HasGHCVariant env) 
=> Maybe (Path Abs File)

Root directory for when url is a filepath

-> Text 
-> m (MiniBuildPlan, SnapshotHash) 

loadBuildPlan :: (StackMiniM env m, HasConfig env) => SnapName -> m BuildPlan Source #

Load the BuildPlan for the given snapshot. Will load from a local copy if available, otherwise downloading from Github.