Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Hix.Managed.Data.StageState
Documentation
data BuildStatus Source #
Instances
Generic BuildStatus Source # | |
Defined in Hix.Managed.Data.StageState Associated Types type Rep BuildStatus :: Type -> Type # | |
Show BuildStatus Source # | |
Defined in Hix.Managed.Data.StageState Methods showsPrec :: Int -> BuildStatus -> ShowS # show :: BuildStatus -> String # showList :: [BuildStatus] -> ShowS # | |
Eq BuildStatus Source # | |
Defined in Hix.Managed.Data.StageState | |
type Rep BuildStatus Source # | |
justSuccess :: a -> BuildStatus -> Maybe a Source #
data BuildResult Source #
Constructors
Finished BuildStatus | |
TimedOut |
Instances
Generic BuildResult Source # | |
Defined in Hix.Managed.Data.StageState Associated Types type Rep BuildResult :: Type -> Type # | |
Show BuildResult Source # | |
Defined in Hix.Managed.Data.StageState Methods showsPrec :: Int -> BuildResult -> ShowS # show :: BuildResult -> String # showList :: [BuildResult] -> ShowS # | |
Eq BuildResult Source # | |
Defined in Hix.Managed.Data.StageState | |
type Rep BuildResult Source # | |
Defined in Hix.Managed.Data.StageState type Rep BuildResult = D1 ('MetaData "BuildResult" "Hix.Managed.Data.StageState" "hix-0.7.1-GF38grEMhDKjpxBMjWXGC" 'False) (C1 ('MetaCons "Finished" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BuildStatus)) :+: C1 ('MetaCons "TimedOut" 'PrefixI 'False) (U1 :: Type -> Type)) |
buildUnsuccessful :: BuildResult -> Bool Source #
buildStatus :: BuildResult -> BuildStatus Source #
data BuildSuccess Source #
Constructors
CandidateBuilt MutableId | |
Unmodified MutableDep |
Instances
Generic BuildSuccess Source # | |
Defined in Hix.Managed.Data.StageState Associated Types type Rep BuildSuccess :: Type -> Type # | |
Show BuildSuccess Source # | |
Defined in Hix.Managed.Data.StageState Methods showsPrec :: Int -> BuildSuccess -> ShowS # show :: BuildSuccess -> String # showList :: [BuildSuccess] -> ShowS # | |
Eq BuildSuccess Source # | |
Defined in Hix.Managed.Data.StageState | |
type Rep BuildSuccess Source # | |
Defined in Hix.Managed.Data.StageState type Rep BuildSuccess = D1 ('MetaData "BuildSuccess" "Hix.Managed.Data.StageState" "hix-0.7.1-GF38grEMhDKjpxBMjWXGC" 'False) (C1 ('MetaCons "CandidateBuilt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 MutableId)) :+: C1 ('MetaCons "Unmodified" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 MutableDep))) |
modifiedCandidates :: [BuildSuccess] -> [MutableId] Source #
data StageState a s Source #
Constructors
StageState | |
Fields
|
Instances
(Show a, Show s) => Show (StageState a s) Source # | |
Defined in Hix.Managed.Data.StageState Methods showsPrec :: Int -> StageState a s -> ShowS # show :: StageState a s -> String # showList :: [StageState a s] -> ShowS # | |
(Eq a, Eq s) => Eq (StageState a s) Source # | |
Defined in Hix.Managed.Data.StageState Methods (==) :: StageState a s -> StageState a s -> Bool # (/=) :: StageState a s -> StageState a s -> Bool # |
initStageState :: Initial MutationState -> s -> StageState a s Source #