stack-1.6.1.1: The Haskell Tool Stack

Safe HaskellNone
LanguageHaskell2010

Stack.Types.Resolver

Synopsis

Documentation

data IsLoaded Source #

Constructors

Loaded 
NotLoaded 

data ResolverWith customContents Source #

How we resolve which dependencies to install given a set of packages.

Constructors

ResolverSnapshot !SnapName

Use an official snapshot from the Stackage project, either an LTS Haskell or Stackage Nightly.

ResolverCompiler !(CompilerVersion CVWanted)

Require a specific compiler version, but otherwise provide no build plan. Intended for use cases where end user wishes to specify all upstream dependencies manually, such as using a dependency solver.

ResolverCustom !Text !customContents

A custom resolver based on the given location (as a raw URL or filepath). If customContents is a Either Request FilePath, it represents the parsed location value (with filepaths resolved relative to the directory containing the file referring to the custom snapshot). Once it has been loaded from disk, it will be replaced with a SnapshotHash value, which is used to store cached files.

Instances

Functor ResolverWith Source # 

Methods

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

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

Foldable ResolverWith Source # 

Methods

fold :: Monoid m => ResolverWith m -> m #

foldMap :: Monoid m => (a -> m) -> ResolverWith a -> m #

foldr :: (a -> b -> b) -> b -> ResolverWith a -> b #

foldr' :: (a -> b -> b) -> b -> ResolverWith a -> b #

foldl :: (b -> a -> b) -> b -> ResolverWith a -> b #

foldl' :: (b -> a -> b) -> b -> ResolverWith a -> b #

foldr1 :: (a -> a -> a) -> ResolverWith a -> a #

foldl1 :: (a -> a -> a) -> ResolverWith a -> a #

toList :: ResolverWith a -> [a] #

null :: ResolverWith a -> Bool #

length :: ResolverWith a -> Int #

elem :: Eq a => a -> ResolverWith a -> Bool #

maximum :: Ord a => ResolverWith a -> a #

minimum :: Ord a => ResolverWith a -> a #

sum :: Num a => ResolverWith a -> a #

product :: Num a => ResolverWith a -> a #

Traversable ResolverWith Source # 

Methods

traverse :: Applicative f => (a -> f b) -> ResolverWith a -> f (ResolverWith b) #

sequenceA :: Applicative f => ResolverWith (f a) -> f (ResolverWith a) #

mapM :: Monad m => (a -> m b) -> ResolverWith a -> m (ResolverWith b) #

sequence :: Monad m => ResolverWith (m a) -> m (ResolverWith a) #

NFData LoadedResolver Source # 

Methods

rnf :: LoadedResolver -> () #

Store LoadedResolver Source # 
Eq customContents => Eq (ResolverWith customContents) Source # 

Methods

(==) :: ResolverWith customContents -> ResolverWith customContents -> Bool #

(/=) :: ResolverWith customContents -> ResolverWith customContents -> Bool #

Data customContents => Data (ResolverWith customContents) Source # 

Methods

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

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

toConstr :: ResolverWith customContents -> Constr #

dataTypeOf :: ResolverWith customContents -> DataType #

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

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

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

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

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

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

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

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

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

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

Show customContents => Show (ResolverWith customContents) Source # 

Methods

showsPrec :: Int -> ResolverWith customContents -> ShowS #

show :: ResolverWith customContents -> String #

showList :: [ResolverWith customContents] -> ShowS #

Generic (ResolverWith customContents) Source # 

Associated Types

type Rep (ResolverWith customContents) :: * -> * #

Methods

from :: ResolverWith customContents -> Rep (ResolverWith customContents) x #

to :: Rep (ResolverWith customContents) x -> ResolverWith customContents #

ToJSON (ResolverWith a) Source # 
(~) * a () => FromJSON (ResolverWith a) Source # 
type Rep (ResolverWith customContents) Source # 

parseResolverText :: Text -> ResolverWith () Source #

Parse a Resolver from a Text

data AbstractResolver Source #

Either an actual resolver value, or an abstract description of one (e.g., latest nightly).

resolverRawName :: ResolverWith a -> Text Source #

Convert a Resolver into its Text representation for human presentation. When possible, you should prefer sdResolverName, as it will handle the human-friendly name inside a custom snapshot.

data SnapName Source #

The name of an LTS Haskell or Stackage Nightly snapshot.

Constructors

LTS !Int !Int 
Nightly !Day 

Instances

Eq SnapName Source # 
Data SnapName Source # 

Methods

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

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

toConstr :: SnapName -> Constr #

dataTypeOf :: SnapName -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SnapName Source # 
Generic SnapName Source # 

Associated Types

type Rep SnapName :: * -> * #

Methods

from :: SnapName -> Rep SnapName x #

to :: Rep SnapName x -> SnapName #

NFData SnapName Source # 

Methods

rnf :: SnapName -> () #

Store SnapName Source # 
type Rep SnapName Source # 

data Snapshots Source #

Most recent Nightly and newest LTS version per major release.

Constructors

Snapshots 

renderSnapName :: SnapName -> Text Source #

Convert a SnapName into its short representation, e.g. lts-2.8, nightly-2015-03-05.

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

Parse the short representation of a SnapName.

data SnapshotHash Source #

Instances

Eq SnapshotHash Source # 
Data SnapshotHash Source # 

Methods

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

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

toConstr :: SnapshotHash -> Constr #

dataTypeOf :: SnapshotHash -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SnapshotHash Source # 
Generic SnapshotHash Source # 

Associated Types

type Rep SnapshotHash :: * -> * #

NFData SnapshotHash Source # 

Methods

rnf :: SnapshotHash -> () #

NFData LoadedResolver Source # 

Methods

rnf :: LoadedResolver -> () #

Store SnapshotHash Source # 
Store LoadedResolver Source # 
type Rep SnapshotHash Source # 
type Rep SnapshotHash = D1 * (MetaData "SnapshotHash" "Stack.Types.Resolver" "stack-1.6.1.1-HaKtsinTMoYAIxQsiG8NSZ" True) (C1 * (MetaCons "SnapshotHash" PrefixI True) (S1 * (MetaSel (Just Symbol "unSnapshotHash") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * StaticSHA256)))

trimmedSnapshotHash :: SnapshotHash -> Text Source #

Return the first 12 characters of the hash as a B64URL-encoded string.

snapshotHashToBS :: SnapshotHash -> ByteString Source #

Return the raw bytes in the hash

snapshotHashFromBS :: ByteString -> SnapshotHash Source #

Create a new SnapshotHash by SHA256 hashing the given contents

snapshotHashFromDigest :: Digest SHA256 -> SnapshotHash Source #

Create a new SnapshotHash from the given digest

parseCustomLocation Source #

Arguments

:: MonadThrow m 
=> Maybe (Path Abs Dir)

directory config value was read from

-> ResolverWith () 
-> m Resolver