| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Puppet.Runner
Description
At the top of the abstraction level, the module exposes all high-end services:
- the preferences container
- the puppet daemon
- the statistic module
- the stdlib functions
- a bunch of pure runners
Naturally nothing from Puppet.Runner should be used in lower abstraction layers.
Synopsis
- data Preferences m = Preferences PuppetDirPaths (PuppetDBAPI m) (Container NativeTypeMethods) (Container ([PValue] -> InterpreterMonad PValue)) (Maybe FilePath) (HashSet Text) Strictness Bool [Text] [Text] (HashSet Text) (Container Text) (Container PValue) (Container PValue) Priority (Maybe FilePath)
- prefPuppetPaths :: forall m. Lens' (Preferences m) PuppetDirPaths
- prefPDB :: forall m m. Lens (Preferences m) (Preferences m) (PuppetDBAPI m) (PuppetDBAPI m)
- prefNatTypes :: forall m. Lens' (Preferences m) (Container NativeTypeMethods)
- prefExtFuncs :: forall m. Lens' (Preferences m) (Container ([PValue] -> InterpreterMonad PValue))
- prefHieraPath :: forall m. Lens' (Preferences m) (Maybe FilePath)
- prefIgnoredmodules :: forall m. Lens' (Preferences m) (HashSet Text)
- prefStrictness :: forall m. Lens' (Preferences m) Strictness
- prefExtraTests :: forall m. Lens' (Preferences m) Bool
- prefKnownusers :: forall m. Lens' (Preferences m) [Text]
- prefKnowngroups :: forall m. Lens' (Preferences m) [Text]
- prefExternalmodules :: forall m. Lens' (Preferences m) (HashSet Text)
- prefPuppetSettings :: forall m. Lens' (Preferences m) (Container Text)
- prefFactsOverride :: forall m. Lens' (Preferences m) (Container PValue)
- prefFactsDefault :: forall m. Lens' (Preferences m) (Container PValue)
- prefLogLevel :: forall m. Lens' (Preferences m) Priority
- prefRebaseFile :: forall m. Lens' (Preferences m) (Maybe FilePath)
- dfPreferences :: FilePath -> IO (Preferences IO)
- data PuppetDirPaths
- class HasPuppetDirPaths c where
- dummyEval :: InterpreterMonad a -> Either PrettyError a
- dummyFacts :: Facts
- dummyInitialState :: InterpreterState
- pureEval :: HashMap (TopLevelType, Text) Statement -> InterpreterMonad a -> (Either PrettyError a, InterpreterState, InterpreterWriter)
- pureEval' :: HashMap (TopLevelType, Text) Statement -> InterpreterState -> Maybe PValue -> InterpreterMonad a -> (Either PrettyError a, InterpreterState, InterpreterWriter)
- pureReader :: HashMap (TopLevelType, Text) Statement -> Maybe PValue -> InterpreterReader Identity
- measure :: MStats -> Text -> IO a -> IO a
- newStats :: IO MStats
- getStats :: MStats -> IO StatsTable
- data StatsPoint = StatsPoint {}
- data MStats
- stdlibFunctions :: Container ([PValue] -> InterpreterMonad PValue)
- data Daemon = Daemon {
- getCatalog :: NodeName -> Facts -> IO (Either PrettyError (FinalCatalog, EdgeMap, FinalCatalog, [Resource]))
- parserStats :: MStats
- catalogStats :: MStats
- templateStats :: MStats
- initDaemon :: Preferences IO -> IO Daemon
- rubyEvaluate :: Container ScopeInformation -> ScopeName -> [RubyStatement] -> Either Doc Text
- module Puppet.Interpreter
Preferences
data Preferences m Source #
Constructors
| Preferences PuppetDirPaths (PuppetDBAPI m) (Container NativeTypeMethods) (Container ([PValue] -> InterpreterMonad PValue)) (Maybe FilePath) (HashSet Text) Strictness Bool [Text] [Text] (HashSet Text) (Container Text) (Container PValue) (Container PValue) Priority (Maybe FilePath) |
prefPuppetPaths :: forall m. Lens' (Preferences m) PuppetDirPaths Source #
prefPDB :: forall m m. Lens (Preferences m) (Preferences m) (PuppetDBAPI m) (PuppetDBAPI m) Source #
prefNatTypes :: forall m. Lens' (Preferences m) (Container NativeTypeMethods) Source #
prefExtFuncs :: forall m. Lens' (Preferences m) (Container ([PValue] -> InterpreterMonad PValue)) Source #
prefHieraPath :: forall m. Lens' (Preferences m) (Maybe FilePath) Source #
prefIgnoredmodules :: forall m. Lens' (Preferences m) (HashSet Text) Source #
prefStrictness :: forall m. Lens' (Preferences m) Strictness Source #
prefExtraTests :: forall m. Lens' (Preferences m) Bool Source #
prefKnownusers :: forall m. Lens' (Preferences m) [Text] Source #
prefKnowngroups :: forall m. Lens' (Preferences m) [Text] Source #
prefExternalmodules :: forall m. Lens' (Preferences m) (HashSet Text) Source #
prefPuppetSettings :: forall m. Lens' (Preferences m) (Container Text) Source #
prefFactsOverride :: forall m. Lens' (Preferences m) (Container PValue) Source #
prefFactsDefault :: forall m. Lens' (Preferences m) (Container PValue) Source #
prefLogLevel :: forall m. Lens' (Preferences m) Priority Source #
prefRebaseFile :: forall m. Lens' (Preferences m) (Maybe FilePath) Source #
dfPreferences :: FilePath -> IO (Preferences IO) Source #
Generate default preferences.
data PuppetDirPaths Source #
Instances
| HasPuppetDirPaths PuppetDirPaths Source # | |
Defined in Puppet.Language.Paths | |
class HasPuppetDirPaths c where Source #
Minimal complete definition
Methods
puppetDirPaths :: Lens' c PuppetDirPaths Source #
baseDir :: Lens' c FilePath Source #
manifestPath :: Lens' c FilePath Source #
modulesPath :: Lens' c FilePath Source #
templatesPath :: Lens' c FilePath Source #
Instances
| HasPuppetDirPaths PuppetDirPaths Source # | |
Defined in Puppet.Language.Paths | |
Pure
dummyEval :: InterpreterMonad a -> Either PrettyError a Source #
A default evaluation function for arbitrary interpreter actions.
Unlike pureEval, each hiera lookup is evaluated to return the string dummy.
dummyFacts :: Facts Source #
A bunch of facts that can be used for pure evaluation.
Arguments
| :: HashMap (TopLevelType, Text) Statement | A top-level map |
| -> InterpreterMonad a | The action to evaluate |
| -> (Either PrettyError a, InterpreterState, InterpreterWriter) |
Evaluates with a map of statements in a pure context.
Unlike dummyEval, each hiera lookup is evaluated to return Nothing.
Arguments
| :: HashMap (TopLevelType, Text) Statement | A top-level map |
| -> InterpreterState | the initial state |
| -> Maybe PValue | a value to be return by all hiera lookup |
| -> InterpreterMonad a | The action to evaluate |
| -> (Either PrettyError a, InterpreterState, InterpreterWriter) |
More flexible version of pureEval
Arguments
| :: HashMap (TopLevelType, Text) Statement | A top-level statement map |
| -> Maybe PValue | What value a call to hiera should return |
| -> InterpreterReader Identity |
A pure InterpreterReader, that can only evaluate a subset of the
templates, and that can include only the supplied top level statements.
Stats
Wraps a computation, and measures related execution statistics.
data StatsPoint Source #
Constructors
| StatsPoint | |
Fields
| |
Instances
| Show StatsPoint Source # | |
Defined in Puppet.Runner.Stats Methods showsPrec :: Int -> StatsPoint -> ShowS # show :: StatsPoint -> String # showList :: [StatsPoint] -> ShowS # | |
Sdlib
stdlibFunctions :: Container ([PValue] -> InterpreterMonad PValue) Source #
Contains the implementation of the StdLib functions.
Daemon
API for the Daemon.
The main method is getCatalog: given a node and a list of facts, it returns the result of the compilation.
This will be either an error, or a tuple containing:
- all the resources in this catalog
- the dependency map
- the exported resources
- a list of known resources, that might not be up to date, but are here for code coverage tests.
Notes :
- It might be buggy when top level statements that are not class/define/nodes are altered.
Constructors
| Daemon | |
Fields
| |
initDaemon :: Preferences IO -> IO Daemon Source #
Entry point to get a Daemon.
It will initialize the parsing and interpretation infrastructure from the Preferences.
Cache the AST of every .pp file. It could use a bit of memory. As a comparison, it fits in 60 MB with the author's manifests, but really breathes when given 300 MB of heap space. In this configuration, even if it spawns a ruby process for every template evaluation, it is way faster than the puppet stack.
It can optionally talk with PuppetDB, by setting an URL via the prefPDB.
The recommended way to set it to http://localhost:8080 and set a SSH tunnel :
ssh -L 8080:localhost:8080 puppet.host
Re-export
rubyEvaluate :: Container ScopeInformation -> ScopeName -> [RubyStatement] -> Either Doc Text Source #
Evaluate a list of ruby statements.
module Puppet.Interpreter