| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Stack.Types.Resolver
Synopsis
- type Resolver = ResolverWith (Either Request FilePath)
 - data IsLoaded
 - type LoadedResolver = ResolverWith SnapshotHash
 - data ResolverWith customContents
- = ResolverStackage !SnapName
 - | ResolverCompiler !(CompilerVersion CVWanted)
 - | ResolverCustom !Text !customContents
 
 - parseResolverText :: Text -> ResolverWith ()
 - data AbstractResolver
- = ARLatestNightly
 - | ARLatestLTS
 - | ARLatestLTSMajor !Int
 - | ARResolver !(ResolverWith ())
 - | ARGlobal
 
 - readAbstractResolver :: ReadM AbstractResolver
 - resolverRawName :: ResolverWith a -> Text
 - data SnapName
 - data Snapshots = Snapshots {
- snapshotsNightly :: !Day
 - snapshotsLts :: !(IntMap Int)
 
 - renderSnapName :: SnapName -> Text
 - parseSnapName :: MonadThrow m => Text -> m SnapName
 - data SnapshotHash
 - trimmedSnapshotHash :: SnapshotHash -> Text
 - snapshotHashToBS :: SnapshotHash -> ByteString
 - snapshotHashFromBS :: ByteString -> SnapshotHash
 - snapshotHashFromDigest :: Digest SHA256 -> SnapshotHash
 - parseCustomLocation :: MonadThrow m => Maybe (Path Abs Dir) -> ResolverWith () -> m Resolver
 
Documentation
data ResolverWith customContents Source #
How we resolve which dependencies to install given a set of packages.
Constructors
| ResolverStackage !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   | 
Instances
| Functor ResolverWith Source # | |
Defined in Stack.Types.Resolver Methods fmap :: (a -> b) -> ResolverWith a -> ResolverWith b # (<$) :: a -> ResolverWith b -> ResolverWith a #  | |
| Foldable ResolverWith Source # | |
Defined in Stack.Types.Resolver 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 # | |
Defined in Stack.Types.Resolver 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 # | |
Defined in Stack.Types.Resolver Methods rnf :: LoadedResolver -> () #  | |
| Store LoadedResolver Source # | |
Defined in Stack.Types.Resolver Methods size :: Size LoadedResolver # poke :: LoadedResolver -> Poke () # peek :: Peek LoadedResolver #  | |
| Eq customContents => Eq (ResolverWith customContents) Source # | |
Defined in Stack.Types.Resolver Methods (==) :: ResolverWith customContents -> ResolverWith customContents -> Bool # (/=) :: ResolverWith customContents -> ResolverWith customContents -> Bool #  | |
| Data customContents => Data (ResolverWith customContents) Source # | |
Defined in Stack.Types.Resolver 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 # | |
Defined in Stack.Types.Resolver Methods showsPrec :: Int -> ResolverWith customContents -> ShowS # show :: ResolverWith customContents -> String # showList :: [ResolverWith customContents] -> ShowS #  | |
| Generic (ResolverWith customContents) Source # | |
Defined in Stack.Types.Resolver Associated Types type Rep (ResolverWith customContents) :: Type -> Type # Methods from :: ResolverWith customContents -> Rep (ResolverWith customContents) x # to :: Rep (ResolverWith customContents) x -> ResolverWith customContents #  | |
| ToJSON (ResolverWith a) Source # | |
Defined in Stack.Types.Resolver Methods toJSON :: ResolverWith a -> Value # toEncoding :: ResolverWith a -> Encoding # toJSONList :: [ResolverWith a] -> Value # toEncodingList :: [ResolverWith a] -> Encoding #  | |
| a ~ () => FromJSON (ResolverWith a) Source # | |
Defined in Stack.Types.Resolver Methods parseJSON :: Value -> Parser (ResolverWith a) # parseJSONList :: Value -> Parser [ResolverWith a] #  | |
| type Rep (ResolverWith customContents) Source # | |
Defined in Stack.Types.Resolver type Rep (ResolverWith customContents) = D1 (MetaData "ResolverWith" "Stack.Types.Resolver" "stack-1.9.3-A8b1pQY9CjdHmL7IWv3q9b" False) (C1 (MetaCons "ResolverStackage" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SnapName)) :+: (C1 (MetaCons "ResolverCompiler" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (CompilerVersion CVWanted))) :+: C1 (MetaCons "ResolverCustom" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 customContents))))  | |
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).
Constructors
| ARLatestNightly | |
| ARLatestLTS | |
| ARLatestLTSMajor !Int | |
| ARResolver !(ResolverWith ()) | |
| ARGlobal | 
Instances
| Show AbstractResolver Source # | |
Defined in Stack.Types.Resolver Methods showsPrec :: Int -> AbstractResolver -> ShowS # show :: AbstractResolver -> String # showList :: [AbstractResolver] -> ShowS #  | |
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.
The name of an LTS Haskell or Stackage Nightly snapshot.
Instances
Most recent Nightly and newest LTS version per major release.
Constructors
| Snapshots | |
Fields 
  | |
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
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
Arguments
| :: MonadThrow m | |
| => Maybe (Path Abs Dir) | directory config value was read from  | 
| -> ResolverWith () | |
| -> m Resolver |