Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Hix.Managed.Cabal.Repo
Documentation
withRepoContextM :: SolveConfig -> GlobalFlags -> (RepoContext -> M a) -> M a Source #
fullHackageRepo :: SolveConfig -> RepoContext -> M Repo Source #
data IndexProblem Source #
Constructors
IndexMissing | |
IndexOutdated | |
IndexMismatch |
Instances
Generic IndexProblem Source # | |
Defined in Hix.Managed.Cabal.Repo Associated Types type Rep IndexProblem :: Type -> Type # | |
Show IndexProblem Source # | |
Defined in Hix.Managed.Cabal.Repo Methods showsPrec :: Int -> IndexProblem -> ShowS # show :: IndexProblem -> String # showList :: [IndexProblem] -> ShowS # | |
Eq IndexProblem Source # | |
Defined in Hix.Managed.Cabal.Repo | |
type Rep IndexProblem Source # | |
Defined in Hix.Managed.Cabal.Repo type Rep IndexProblem = D1 ('MetaData "IndexProblem" "Hix.Managed.Cabal.Repo" "hix-0.7.0-1RsI1H0rYs1Kacz9sjlUfZ" 'False) (C1 ('MetaCons "IndexMissing" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "IndexOutdated" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IndexMismatch" 'PrefixI 'False) (U1 :: Type -> Type))) |
updateRequest :: SolveConfig -> String Source #
updateIndex :: SolveConfig -> GlobalFlags -> NixStyleFlags () -> IndexProblem -> M () Source #
matchIndexState :: Verbosity -> RepoContext -> Repo -> HackageIndexState -> M (Maybe IndexProblem) Source #
indexProblem :: SolveConfig -> RepoContext -> Repo -> Path Abs File -> M (Maybe IndexProblem) Source #
ensureHackageIndex :: SolveConfig -> GlobalFlags -> NixStyleFlags () -> M () Source #