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

Safe HaskellNone
LanguageHaskell98

Puppet.Interpreter.Types

Synopsis

Documentation

data HieraQueryType Source

The different kind of hiera queries

Constructors

Priority

standard hiera query

ArrayMerge

hiera_array

HashMerge

hiera_hash

type HieraQueryFunc m Source

Arguments

 = Container Text

All the variables that Hiera can interpolate, the top level ones being prefixed with ::

-> Text

The query

-> HieraQueryType 
-> m (Either PrettyError (Pair InterpreterWriter (Maybe PValue))) 

The type of the Hiera API function

data TopLevelType Source

This type is used to differenciate the distinct top level types that are exposed by the DSL.

Constructors

TopNode

This is for node entries.

TopDefine

This is for defines.

TopClass

This is for classes.

TopSpurious

This one is special. It represents top level statements that are not part of a node, define or class. It is defined as spurious because it is not what you are supposed to be. Also the caching system doesn't like them too much right now.

data CurContainerDesc Source

Constructors

ContRoot

Contained at node or root level

ContClass !Text

Contained in a class

ContDefine !Text !Text !PPosition

Contained in a define, along with the position where this define was ... defined

ContImported !CurContainerDesc

Dummy container for imported resources, so that we know we must update the nodename

ContImport !Nodename !CurContainerDesc

This one is used when finalizing imported resources, and contains the current node name

data InterpreterInstr a where Source

Constructors

GetNativeTypes :: InterpreterInstr (Container NativeTypeMethods) 
GetStatement :: TopLevelType -> Text -> InterpreterInstr Statement 
ComputeTemplate :: Either Text Text -> Text -> Container ScopeInformation -> InterpreterInstr Text 
ExternalFunction :: Text -> [PValue] -> InterpreterInstr PValue 
GetNodeName :: InterpreterInstr Text 
HieraQuery :: Container Text -> Text -> HieraQueryType -> InterpreterInstr (Pair InterpreterWriter (Maybe PValue)) 
GetCurrentCallStack :: InterpreterInstr [String] 
IsIgnoredModule :: Text -> InterpreterInstr Bool 
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 [PFactInfo] 
PDBGetResources :: Query ResourceField -> InterpreterInstr [Resource] 
PDBGetNodes :: Query NodeField -> InterpreterInstr [PNodeInfo] 
PDBCommitDB :: InterpreterInstr () 
PDBGetResourcesOfNode :: Nodename -> Query ResourceField -> InterpreterInstr [Resource] 
ReadFile :: [Text] -> InterpreterInstr Text 
TraceEvent :: String -> InterpreterInstr () 
CallLua :: MVar LuaState -> Text -> [PValue] -> InterpreterInstr PValue 

newtype Warning Source

Constructors

Warning Doc 

data ModifierType Source

Constructors

ModifierCollector

For collectors, optional resources

ModifierMustMatch

For stuff like realize

Instances

data OverrideType Source

Constructors

CantOverride

Overriding forbidden, will throw an error

Replace

Can silently replace

CantReplace

Silently ignore errors

data Resource Source

This is a fully resolved resource that will be used in the FinalCatalog.

Constructors

Resource 

Fields

_rid :: !RIdentifier

Resource name.

_ralias :: !(HashSet Text)

All the resource aliases

_rattributes :: !(Container PValue)

Resource parameters.

_rrelations :: !(HashMap RIdentifier (HashSet LinkType))

Resource relations.

_rscope :: ![CurContainerDesc]

Resource scope when it was defined, the real container will be the first item

_rvirtuality :: !Virtuality
 
_rtags :: !(HashSet Text)
 
_rpos :: !PPosition

Source code position of the resource definition.

_rnode :: !Nodename

The node were this resource was created, if remote

data NativeTypeMethods Source

Attributes (and providers) of a puppet resource type bundled with validation rules

data DaemonMethods Source

Constructors

DaemonMethods 

Fields

_dGetCatalog :: Text -> Facts -> IO (Either PrettyError (FinalCatalog, EdgeMap, FinalCatalog, [Resource]))

The most important function, computing catalogs. Given a node name and a list of facts, it returns the result of the catalog compilation : either an error, or a tuple containing all the resources in this catalog, the dependency map, the exported resources, and a list of known resources, that might not be up to date, but are here for code coverage tests.

_dParserStats :: MStats
 
_dCatalogStats :: MStats
 
_dTemplateStats :: MStats
 

data Query a Source

Pretty straightforward way to define the various PuppetDB queries

Constructors

QEqual a Text 
QG a Integer 
QL a Integer 
QGE a Integer 
QLE a Integer 
QMatch Text Text 
QAnd [Query a] 
QOr [Query a] 
QNot (Query a) 
QEmpty 

Instances

ToJSON a => ToJSON (Query a) 
FromJSON a => FromJSON (Query a) 

data FactField Source

Fields for the fact endpoint

Constructors

FName 
FValue 
FCertname 

data NodeField Source

Fields for the node endpoint

Constructors

NName 
NFact Text 

data ResourceField Source

Fields for the resource endpoint

class HasWEdges s a | s -> a where Source

Methods

wEdges :: Lens' s a Source

class HasWResources s a | s -> a where Source

Methods

wResources :: Lens' s a Source

class HasWVersion s a | s -> a where Source

Methods

wVersion :: Lens' s a Source

class HasFactname s a | s -> a where Source

Methods

factname :: Lens' s a Source

class HasFactval s a | s -> a where Source

Methods

factval :: Lens' s a Source

class HasCatalogT s a | s -> a where Source

Methods

catalogT :: Lens' s a Source

class HasDeactivated s a | s -> a where Source

Methods

deactivated :: Lens' s a Source

class HasFactsT s a | s -> a where Source

Methods

factsT :: Lens' s a Source

class HasReportT s a | s -> a where Source

Methods

reportT :: Lens' s a Source

ifromList :: (Monoid m, At m, Foldable f) => f (Index m, IxValue m) -> m Source

helper for hashmap, in case we want another kind of map ..

ikeys :: (Eq k, Hashable k) => HashMap k v -> HashSet k Source

isingleton :: (Monoid b, At b) => Index b -> IxValue b -> b Source

ifromListWith :: (Monoid m, At m, Foldable f) => (IxValue m -> IxValue m -> IxValue m) -> f (Index m, IxValue m) -> m Source

iinsertWith :: At m => (IxValue m -> IxValue m -> IxValue m) -> Index m -> IxValue m -> m -> m Source

iunionWith :: (Hashable k, Eq k) => (v -> v -> v) -> HashMap k v -> HashMap k v -> HashMap k v Source

fnull :: (Eq x, Monoid x) => x -> Bool Source