deptrack-devops-0.1.0.0: DepTrack applied to DevOps.

Safe HaskellSafe
LanguageHaskell2010

Devops.Base

Synopsis

Documentation

data PreOp Source #

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

Constructors

Typeable a => PreOp !a !(a -> Op) 
Instances
Eq PreOp Source # 
Instance details

Defined in Devops.Base

Methods

(==) :: PreOp -> PreOp -> Bool #

(/=) :: PreOp -> PreOp -> Bool #

Show PreOp Source # 
Instance details

Defined in Devops.Base

Methods

showsPrec :: Int -> PreOp -> ShowS #

show :: PreOp -> String #

showList :: [PreOp] -> ShowS #

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.

data Op Source #

An actual system-level operation that can be tracked and depended on. Ops 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.

Instances
Show Op Source # 
Instance details

Defined in Devops.Base

Methods

showsPrec :: Int -> Op -> ShowS #

show :: Op -> String #

showList :: [Op] -> ShowS #

data OpDescription Source #

Constructors

OpDescription 

Fields

Instances
Eq OpDescription Source # 
Instance details

Defined in Devops.Base

Ord OpDescription Source # 
Instance details

Defined in Devops.Base

Show OpDescription Source # 
Instance details

Defined in Devops.Base

Generic OpDescription Source # 
Instance details

Defined in Devops.Base

Associated Types

type Rep OpDescription :: * -> * #

Hashable OpDescription Source # 
Instance details

Defined in Devops.Base

type Rep OpDescription Source # 
Instance details

Defined in Devops.Base

type Rep OpDescription = D1 (MetaData "OpDescription" "Devops.Base" "deptrack-devops-0.1.0.0-1BQsWDMcJxoKhJobugMn50" False) (C1 (MetaCons "OpDescription" PrefixI True) (S1 (MetaSel (Just "opName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Name) :*: S1 (MetaSel (Just "opDocumentation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

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).

type DevOpT e m = ReaderT e (DepTrackT PreOp m) Source #

Handy name for tracking DevOp dependencies.

runPreOp :: PreOp -> Op Source #

Applies the argument and the function in a PreOp to get an Op.

preopType :: PreOp -> TypeRep Source #

Reads the runtime representation of the PreOp argument.

This function is useful to display or filter dependency nodes at runtime.

preOpUniqueId :: PreOp -> OpUniqueId Source #

The identifier for a PreOp.

data CheckResult Source #

Constructors

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

fromBool :: Bool -> CheckResult Source #

Transforms True into Success, False into a Failure.

type OpAction = IO () Source #

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.

noop :: Name -> Text -> PreOp Source #

Returns a noop.

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.

type Name = Text Source #

track :: Monad m => (a -> PreOp) -> DevOpT e m a -> DevOpT e m a Source #

declare :: Monad m => PreOp -> DevOpT e m a -> DevOpT e m a Source #

inject :: Monad m => DevOpT e m a -> DevOpT e m b -> DevOpT e m (a, b) Source #

guardEnv :: (Monad m, Alternative m) => (e -> Bool) -> DevOpT e m () Source #

runDevOp :: env -> DevOp env a -> Maybe a Source #

Evaluates the return value of a DevOp, discarding the dependencies.

getDependenciesOnly :: env -> DevOp env a -> Forest PreOp Source #

Evaluates the dependencies of a DevOp, discarding any result.