| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Stack.Types.Resolver
Synopsis
- data AbstractResolver
- readAbstractResolver :: ReadM (Unresolved AbstractResolver)
- data SnapName
- data Snapshots = Snapshots {
- snapshotsNightly :: !Day
- snapshotsLts :: !(IntMap Int)
- renderSnapName :: SnapName -> Text
- parseSnapName :: MonadThrow m => Text -> m SnapName
Documentation
data AbstractResolver Source #
Either an actual resolver value, or an abstract description of one (e.g., latest nightly).
Constructors
| ARLatestNightly | |
| ARLatestLTS | |
| ARLatestLTSMajor !Int | |
| ARResolver !RawSnapshotLocation | |
| ARGlobal |
Instances
| Show AbstractResolver Source # | |
Defined in Stack.Types.Resolver Methods showsPrec :: Int -> AbstractResolver -> ShowS # show :: AbstractResolver -> String # showList :: [AbstractResolver] -> ShowS # | |
| Display AbstractResolver Source # | |
Defined in Stack.Types.Resolver | |
The name of an LTS Haskell or Stackage Nightly snapshot.
Instances
| Eq SnapName Source # | |
| Data SnapName Source # | |
Defined in Stack.Types.Resolver 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 # | |
| NFData SnapName Source # | |
Defined in Stack.Types.Resolver | |
| Display SnapName Source # | |
Defined in Stack.Types.Resolver | |
| type Rep SnapName Source # | |
Defined in Stack.Types.Resolver type Rep SnapName = D1 (MetaData "SnapName" "Stack.Types.Resolver" "stack-2.1.1-61yUJamJcYLHh5iq4tOGPX" False) (C1 (MetaCons "LTS" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) :+: C1 (MetaCons "Nightly" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Day))) | |
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.