language-puppet-1.4.5: Tools to parse and evaluate the Puppet DSL.

Safe HaskellNone
LanguageHaskell98

Puppet.Interpreter

Contents

Synopsis

Documentation

interpretCatalog Source #

Arguments

:: Monad m 
=> InterpreterReader m

The whole environment required for computing catalog.

-> NodeName 
-> Facts 
-> Container Text

Server settings

-> m (Pair (Either PrettyError (FinalCatalog, EdgeMap, FinalCatalog, [Resource])) [Pair Priority Doc]) 

Call the operational interpretMonad function to compute the catalog. Returns either an error, or a tuple containing all the resources, dependency map, exported resources, and defined resources alongside with all messages that have been generated by the compilation process.

The later defined resources (eg. all class declarations) are pulled out of the InterpreterState and might not be up to date. There are only useful for coverage testing (checking dependencies for instance).

computeCatalog :: NodeName -> InterpreterMonad (FinalCatalog, EdgeMap, FinalCatalog, [Resource]) Source #

Main internal entry point, this function completes the interpretation

Utils

initialState Source #

Arguments

:: Facts 
-> Container Text

Server settings

-> InterpreterState 

askFact :: Text -> InterpreterMonad (Maybe PValue) Source #

Ask the value of a fact given a specified key The fact set comes from the reader used by the interpreter monad.

Operational state

Operational reader

Interpreter monad

data InterpreterInstr a where Source #

Constructors

GetNativeTypes :: InterpreterInstr (Container NativeTypeMethods) 
GetStatement :: TopLevelType -> Text -> InterpreterInstr Statement 
ComputeTemplate :: TemplateSource -> InterpreterState -> InterpreterInstr Text 
ExternalFunction :: Text -> [PValue] -> InterpreterInstr PValue 
Facts :: InterpreterInstr (Container PValue) 
GetNodeName :: InterpreterInstr Text 
HieraQuery :: Container PValue -> Text -> HieraQueryType -> InterpreterInstr (Maybe PValue) 
GetCurrentCallStack :: InterpreterInstr [String] 
IsIgnoredModule :: Text -> InterpreterInstr Bool 
IsExternalModule :: Text -> InterpreterInstr Bool 
IsStrict :: InterpreterInstr Bool 
PuppetPaths :: InterpreterInstr PuppetDirPaths 
RebaseFile :: InterpreterInstr (Maybe FilePath) 
ErrorThrow :: PrettyError -> InterpreterInstr a 
ErrorCatch :: InterpreterMonad a -> (PrettyError -> InterpreterMonad a) -> InterpreterInstr a 
WriterTell :: InterpreterWriter -> InterpreterInstr () 
WriterPass :: InterpreterMonad (a, InterpreterWriter -> InterpreterWriter) -> InterpreterInstr a 
WriterListen :: InterpreterMonad a -> InterpreterInstr (a, InterpreterWriter) 
PDBInformation :: InterpreterInstr Doc 
PDBReplaceCatalog :: WireCatalog -> InterpreterInstr () 
PDBReplaceFacts :: [(NodeName, Facts)] -> InterpreterInstr () 
PDBDeactivateNode :: NodeName -> InterpreterInstr () 
PDBGetFacts :: Query FactField -> InterpreterInstr [FactInfo] 
PDBGetResources :: Query ResourceField -> InterpreterInstr [Resource] 
PDBGetNodes :: Query NodeField -> InterpreterInstr [NodeInfo] 
PDBCommitDB :: InterpreterInstr () 
PDBGetResourcesOfNode :: NodeName -> Query ResourceField -> InterpreterInstr [Resource] 
ReadFile :: [Text] -> InterpreterInstr Text 
TraceEvent :: String -> InterpreterInstr () 

data Strictness Source #

The intepreter can run in two modes : a strict mode (recommended), and a permissive mode.

Constructors

Strict 
Permissive 

Io methods

data IoMethods m Source #

Constructors

IoMethods (m [String]) ([Text] -> m (Either String Text)) (String -> m ()) 

ioReadFile :: forall m. Lens' (IoMethods m) ([Text] -> m (Either String Text)) Source #

ioTraceEvent :: forall m. Lens' (IoMethods m) (String -> m ()) Source #

class Monad m => MonadThrowPos m where Source #

Methods

throwPosError :: Doc -> m a Source #

Resource modifier

data ModifierType Source #

Constructors

ModifierCollector

For collectors, optional resources

ModifierMustMatch

For stuff like realize

data OverrideType Source #

Constructors

CantOverride

Overriding forbidden, will throw an error

Replace

Can silently replace

CantReplace

Silently ignore errors

AppendAttribute

Can append values

data ClassIncludeType Source #

Puppet has two main ways to declare classes: include-like and resource-like.

See puppet reference.

Constructors

ClassIncludeLike

Using the include or contain function

ClassResourceLike

Resource like declaration

Scope information

data CurContainer Source #

The type of the container together with its tags.

Instances
Eq CurContainer Source # 
Instance details

Defined in Puppet.Interpreter.Types

Resource default

data ResDefaults Source #

From the evaluation of Resource Default Declaration.

Instances
Pretty ResDefaults Source # 
Instance details

Defined in Puppet.Interpreter.PrettyPrinter

data ResRefOverride Source #

From the evaluation of Resource Override Declaration.

data ScopeEnteringContext Source #

Constructors

SENormal 
SEChild !Text

We enter the scope as the child of another class

SEParent !Text

We enter the scope as the parent of another class

data TopLevelType Source #

Differentiate the distinct top level types such as node, define or class.

Constructors

TopNode

For node entries

TopDefine

For defines

TopClass

For classes

Instances
Eq TopLevelType Source # 
Instance details

Defined in Puppet.Interpreter.Types

Generic TopLevelType Source # 
Instance details

Defined in Puppet.Interpreter.Types

Associated Types

type Rep TopLevelType :: Type -> Type #

Hashable TopLevelType Source # 
Instance details

Defined in Puppet.Interpreter.Types

Pretty TopLevelType Source # 
Instance details

Defined in Puppet.Interpreter.PrettyPrinter

type Rep TopLevelType Source # 
Instance details

Defined in Puppet.Interpreter.Types

type Rep TopLevelType = D1 (MetaData "TopLevelType" "Puppet.Interpreter.Types" "language-puppet-1.4.5-5ocbCGkY0q25Rp10ZMtz6b" False) (C1 (MetaCons "TopNode" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "TopDefine" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TopClass" PrefixI False) (U1 :: Type -> Type)))

Hiera

data HieraQueryLayers m Source #

All available queries including the global and module layer The environment layer is not implemented.

The datatype belongs to the Puppet.Interpreter module because it serves to implement how Hiera is used within Puppet.

Template

data TemplateSource Source #

Whether the template source is specified inline or loaded from a file.

Constructors

Inline Text 
Filename FilePath 

Re-export

Pure resolution functions

getVariable Source #

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 #

Turns a PValue into a Bool as explained in the reference documentation.

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

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

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.

fixResourceName Source #

Arguments

:: Text

Resource type

-> Text

Resource name

-> Text 

Converts class resource names to lowercase (fix for the jenkins plugin).

datatypeMatch :: DataType -> PValue -> Bool Source #

Checks that a value matches a puppet datatype