Safe Haskell | None |
---|---|
Language | Haskell98 |
Puppet.Interpreter.Resolve
Contents
Description
This module is all about converting and resolving foreign data into
the fully exploitable corresponding data type. The main use case is the
conversion of Expression
to PValue
.
- getVariable :: Container ScopeInformation -> Text -> Text -> Either Doc PValue
- pValue2Bool :: PValue -> Bool
- resolveVariable :: Text -> InterpreterMonad PValue
- resolveExpression :: Expression -> InterpreterMonad PValue
- resolveValue :: UnresolvedValue -> InterpreterMonad PValue
- resolvePValueString :: PValue -> InterpreterMonad Text
- resolvePValueNumber :: PValue -> InterpreterMonad Scientific
- resolveExpressionString :: Expression -> InterpreterMonad Text
- resolveExpressionStrings :: Expression -> InterpreterMonad [Text]
- resolveFunction' :: Text -> [PValue] -> InterpreterMonad PValue
- runHiera :: Text -> HieraQueryType -> InterpreterMonad (Maybe PValue)
- isNativeType :: Text -> InterpreterMonad Bool
- resolveSearchExpression :: SearchExpression -> InterpreterMonad RSearchExpression
- checkSearchExpression :: RSearchExpression -> Resource -> Bool
- searchExpressionToPuppetDB :: Text -> RSearchExpression -> Query ResourceField
- hfGenerateAssociations :: HOLambdaCall -> InterpreterMonad [[(Text, PValue)]]
- hfSetvars :: [(Text, PValue)] -> InterpreterMonad (Container (Pair (Pair PValue PPosition) CurContainerDesc))
- hfRestorevars :: Container (Pair (Pair PValue PPosition) CurContainerDesc) -> InterpreterMonad ()
- toNumbers :: PValue -> PValue -> Maybe NumberPair
- fixResourceName :: Text -> Text -> Text
Pure resolution functions
Arguments
:: Container ScopeInformation | The whole scope data. |
-> Text | Current scope name. |
-> Text | Full variable name. |
-> Either Doc PValue |
A pure function for resolving variables.
pValue2Bool :: PValue -> Bool Source
Monadic resolution functions
resolveVariable :: Text -> InterpreterMonad PValue Source
Resolves a variable, or throws an error if it can't.
resolveExpression :: Expression -> InterpreterMonad PValue Source
The main resolution function : turns an Expression
into a PValue
,
if possible.
resolveValue :: UnresolvedValue -> InterpreterMonad PValue Source
Resolves an UnresolvedValue
(terminal for the Expression
data type) into
a PValue
resolvePValueString :: PValue -> InterpreterMonad Text Source
Turns strings, numbers and booleans into Text
, or throws an error.
resolvePValueNumber :: PValue -> InterpreterMonad Scientific Source
Turns everything it can into a number, or throws an error
resolveExpressionString :: Expression -> InterpreterMonad Text Source
resolveExpressionString = resolveExpression >=> resolvePValueString
resolveExpressionStrings :: Expression -> InterpreterMonad [Text] Source
Just like resolveExpressionString
, but accepts arrays.
resolveFunction' :: Text -> [PValue] -> InterpreterMonad PValue Source
runHiera :: Text -> HieraQueryType -> InterpreterMonad (Maybe PValue) Source
A hiera helper function, that will throw all Hiera errors and log messages to the main monad.
isNativeType :: Text -> InterpreterMonad Bool Source
A simple helper that checks if a given type is native or a define.
Search expression management
resolveSearchExpression :: SearchExpression -> InterpreterMonad RSearchExpression Source
Turns an unresolved SearchExpression
from the parser into a fully
resolved RSearchExpression
.
checkSearchExpression :: RSearchExpression -> Resource -> Bool Source
Checks whether a given Resource
matches a RSearchExpression
. Note
that the expression doesn't check for type, so you must filter the
resources by type beforehand, if needs be.
searchExpressionToPuppetDB :: Text -> RSearchExpression -> Query ResourceField Source
Turns a resource type and RSearchExpression
into something that can
be used in a PuppetDB query.
Higher order puppet functions handling
hfGenerateAssociations :: HOLambdaCall -> InterpreterMonad [[(Text, PValue)]] Source
Generates variable associations for evaluation of blocks. Each item corresponds to an iteration in the calling block.
hfSetvars :: [(Text, PValue)] -> InterpreterMonad (Container (Pair (Pair PValue PPosition) CurContainerDesc)) Source
Sets the proper variables, and returns the scope variables the way they were before being modified. This is a hack that ensures that variables are local to the new scope.
It doesn't work at all like other Puppet parts, but consistency isn't really expected here ...
hfRestorevars :: Container (Pair (Pair PValue PPosition) CurContainerDesc) -> InterpreterMonad () Source
Restores what needs restoring. This will erase all allocations.
toNumbers :: PValue -> PValue -> Maybe NumberPair Source
Tries to convert a pair of PValue
s into Number
s, as defined in
attoparsec. If the two values can be converted, it will convert them so
that they are of the same type
Arguments
:: Text | Resource type |
-> Text | Resource name |
-> Text |
Converts class resource names to lowercase (fix for the jenkins plugin).