Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- data PreOp = Typeable a => PreOp !a !(a -> Op)
- rawpreop :: Typeable a => a -> (a -> Op) -> PreOp
- data Op = Op {}
- data OpDescription = OpDescription {
- opName :: !Name
- opDocumentation :: !Text
- data OpFunctions = OpFunctions {}
- type DevOp env = DevOpT env []
- type DevOpT e m = ReaderT e (DepTrackT PreOp m)
- runPreOp :: PreOp -> Op
- preopType :: PreOp -> TypeRep
- type OpUniqueId = Int
- preOpUniqueId :: PreOp -> OpUniqueId
- type OpCheck = IO CheckResult
- data CheckResult
- fromBool :: Bool -> CheckResult
- noCheck :: OpCheck
- type OpAction = IO ()
- noAction :: OpAction
- buildOp :: Name -> Text -> OpCheck -> OpAction -> OpAction -> OpAction -> Op
- buildPreOp :: Name -> Text -> OpCheck -> OpAction -> OpAction -> OpAction -> PreOp
- noop :: Name -> Text -> PreOp
- neutralize :: Op -> PreOp
- type TypedPreOp a = (a, a -> Op)
- castPreop :: Typeable a => Proxy a -> PreOp -> Maybe (TypedPreOp a)
- devop :: (Typeable b, Monad m) => (a -> b) -> (a -> Op) -> DevOpT e m a -> DevOpT e m b
- type Name = Text
- track :: Monad m => (a -> PreOp) -> DevOpT e m a -> DevOpT e m a
- declare :: Monad m => PreOp -> DevOpT e m a -> DevOpT e m a
- inject :: Monad m => DevOpT e m a -> DevOpT e m b -> DevOpT e m (a, b)
- guardEnv :: (Monad m, Alternative m) => (e -> Bool) -> DevOpT e m ()
- runDevOp :: env -> DevOp env a -> Maybe a
- getDependenciesOnly :: env -> DevOp env a -> Forest PreOp
Documentation
Encapsulates a deferred Op
along with an a
argument to generate it.
The PreOp is more or less a continuation to produce an Op (which is a set of actions to turnup/turndown system states).
This definition uses existential quantification with a Typeable constraint: * generally, we do not care about the intermediate type * however, we may want to inspect dependency nodes to apply some tree/graph conversion * we don't want to explicitly require library users to create a gigantic sum-type
rawpreop :: Typeable a => a -> (a -> Op) -> PreOp Source #
Projects a Typeable object to a Preop using a projection function. This is a low-level projection function.
An actual system-level operation that can be tracked and depended on.
Op
s provide standard OpFunctions
for actually enacting commands. They are
identified by a OpUniqueId
which is, as it name implies, is guaranteed to be unique
across a whole DepTrack
graph.
Op | |
|
data OpDescription Source #
OpDescription | |
|
Instances
data OpFunctions Source #
Functions that can be run on an Op
object, e.g. a system dependency to enact
commands.
type DevOp env = DevOpT env [] Source #
Handy name for tracking DevOp dependencies using a pure computation (recommended).
preopType :: PreOp -> TypeRep Source #
Reads the runtime representation of the PreOp argument.
This function is useful to display or filter dependency nodes at runtime.
type OpUniqueId = Int Source #
preOpUniqueId :: PreOp -> OpUniqueId Source #
The identifier for a PreOp.
type OpCheck = IO CheckResult Source #
data CheckResult Source #
Skipped | the Check was skipped (e.g., it's not meaningful or the actions are idempotent and cheap => checking is not useful) |
Unknown | the Check has not taken place or not succeeded for unknown reasons |
Success | the Check finished and determined a success |
Failure !Reason | the Check finished and determined a failure |
Instances
Eq CheckResult Source # | |
Defined in Devops.Base (==) :: CheckResult -> CheckResult -> Bool # (/=) :: CheckResult -> CheckResult -> Bool # | |
Ord CheckResult Source # | |
Defined in Devops.Base compare :: CheckResult -> CheckResult -> Ordering # (<) :: CheckResult -> CheckResult -> Bool # (<=) :: CheckResult -> CheckResult -> Bool # (>) :: CheckResult -> CheckResult -> Bool # (>=) :: CheckResult -> CheckResult -> Bool # max :: CheckResult -> CheckResult -> CheckResult # min :: CheckResult -> CheckResult -> CheckResult # | |
Read CheckResult Source # | |
Defined in Devops.Base readsPrec :: Int -> ReadS CheckResult # readList :: ReadS [CheckResult] # readPrec :: ReadPrec CheckResult # readListPrec :: ReadPrec [CheckResult] # | |
Show CheckResult Source # | |
Defined in Devops.Base showsPrec :: Int -> CheckResult -> ShowS # show :: CheckResult -> String # showList :: [CheckResult] -> ShowS # |
fromBool :: Bool -> CheckResult Source #
Transforms True into Success, False into a Failure.
buildOp :: Name -> Text -> OpCheck -> OpAction -> OpAction -> OpAction -> Op Source #
Build the internal representation for an Op
.
buildPreOp :: Name -> Text -> OpCheck -> OpAction -> OpAction -> OpAction -> PreOp Source #
Build the internal representation for a PreOp
.
neutralize :: Op -> PreOp Source #
Takes an Op and makes it a PreOp with same description but with noop checks and actions.
type TypedPreOp a = (a, a -> Op) Source #
Almost like a PreOp, but which exposes the type of the intermediary value.
castPreop :: Typeable a => Proxy a -> PreOp -> Maybe (TypedPreOp a) Source #
Convert a PreOp to a TypedPreOp at runtime.
devop :: (Typeable b, Monad m) => (a -> b) -> (a -> Op) -> DevOpT e m a -> DevOpT e m b Source #
Tracks dependencies to build an object given a pair of projection -- functions and a DepTrackT computation tracking predecessors.