| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Puppet.Interpreter.Types
- metaparameters :: HashSet Text
- type Nodename = Text
- type Container = HashMap Text
- newtype PrettyError = PrettyError {}
- data PValue
- data HieraQueryType
- type HieraQueryFunc m = Container Text -> Text -> HieraQueryType -> m (Either PrettyError (Pair InterpreterWriter (Maybe PValue)))
- data RSearchExpression
- data ClassIncludeType
- type Scope = Text
- type Facts = Container PValue
- data TopLevelType
- data ResDefaults = ResDefaults {
- _defType :: !Text
- _defSrcScope :: !Text
- _defValues :: !(Container PValue)
- _defPos :: !PPosition
- data CurContainerDesc
- data CurContainer = CurContainer {
- _cctype :: !CurContainerDesc
- _cctags :: !(HashSet Text)
- data ResRefOverride = ResRefOverride {}
- data ScopeInformation = ScopeInformation {}
- data InterpreterState = InterpreterState {
- _scopes :: !(Container ScopeInformation)
- _loadedClasses :: !(Container (Pair ClassIncludeType PPosition))
- _definedResources :: !(HashMap RIdentifier Resource)
- _curScope :: ![CurContainerDesc]
- _curPos :: !PPosition
- _nestedDeclarations :: !(HashMap (TopLevelType, Text) Statement)
- _extraRelations :: ![LinkInformation]
- _resMod :: ![ResourceModifier]
- data InterpreterReader m = InterpreterReader {
- _nativeTypes :: !(Container NativeTypeMethods)
- _getStatement :: TopLevelType -> Text -> m (Either PrettyError Statement)
- _computeTemplateFunction :: Either Text Text -> Text -> Container ScopeInformation -> m (Either PrettyError Text)
- _pdbAPI :: PuppetDBAPI m
- _externalFunctions :: Container ([PValue] -> InterpreterMonad PValue)
- _thisNodename :: Text
- _hieraQuery :: HieraQueryFunc m
- _ioMethods :: ImpureMethods m
- _ignoredModules :: HashSet Text
- data ImpureMethods m = ImpureMethods {
- _imGetCurrentCallStack :: m [String]
- _imReadFile :: [Text] -> m (Either String Text)
- _imTraceEvent :: String -> m ()
- _imCallLua :: MVar LuaState -> Text -> [PValue] -> m (Either String PValue)
- data InterpreterInstr a where
- 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 = Warning Doc
- type InterpreterLog = Pair Priority Doc
- type InterpreterWriter = [InterpreterLog]
- warn :: (Monad m, MonadWriter InterpreterWriter m) => Doc -> m ()
- debug :: (Monad m, MonadWriter InterpreterWriter m) => Doc -> m ()
- logWriter :: (Monad m, MonadWriter InterpreterWriter m) => Priority -> Doc -> m ()
- type InterpreterMonad = ProgramT InterpreterInstr (State InterpreterState)
- data RIdentifier = RIdentifier {}
- data ModifierType
- data OverrideType
- data ResourceCollectorType
- data ResourceModifier = ResourceModifier {}
- data LinkInformation = LinkInformation {
- _linksrc :: !RIdentifier
- _linkdst :: !RIdentifier
- _linkType :: !LinkType
- _linkPos :: !PPosition
- type EdgeMap = HashMap RIdentifier [LinkInformation]
- data Resource = Resource {
- _rid :: !RIdentifier
- _ralias :: !(HashSet Text)
- _rattributes :: !(Container PValue)
- _rrelations :: !(HashMap RIdentifier (HashSet LinkType))
- _rscope :: ![CurContainerDesc]
- _rvirtuality :: !Virtuality
- _rtags :: !(HashSet Text)
- _rpos :: !PPosition
- _rnode :: !Nodename
- type NativeTypeValidate = Resource -> Either PrettyError Resource
- data NativeTypeMethods = NativeTypeMethods {}
- type FinalCatalog = HashMap RIdentifier Resource
- data DaemonMethods = DaemonMethods {
- _dGetCatalog :: Text -> Facts -> IO (Either PrettyError (FinalCatalog, EdgeMap, FinalCatalog, [Resource]))
- _dParserStats :: MStats
- _dCatalogStats :: MStats
- _dTemplateStats :: MStats
- data PuppetEdge = PuppetEdge RIdentifier RIdentifier LinkType
- data WireCatalog = WireCatalog {}
- data PFactInfo = PFactInfo {}
- data PNodeInfo = PNodeInfo {}
- data PuppetDBAPI m = PuppetDBAPI {
- pdbInformation :: m Doc
- replaceCatalog :: WireCatalog -> m (Either PrettyError ())
- replaceFacts :: [(Nodename, Facts)] -> m (Either PrettyError ())
- deactivateNode :: Nodename -> m (Either PrettyError ())
- getFacts :: Query FactField -> m (Either PrettyError [PFactInfo])
- getResources :: Query ResourceField -> m (Either PrettyError [Resource])
- getNodes :: Query NodeField -> m (Either PrettyError [PNodeInfo])
- commitDB :: m (Either PrettyError ())
- getResourcesOfNode :: Nodename -> Query ResourceField -> m (Either PrettyError [Resource])
- data Query a
- data FactField
- data NodeField
- data ResourceField
- class HasRIdentifier c where
- rIdentifier :: Lens' c RIdentifier
- iname :: Lens' c Text
- itype :: Lens' c Text
- class HasResRefOverride c where
- resRefOverride :: Lens' c ResRefOverride
- rrid :: Lens' c RIdentifier
- rrparams :: Lens' c (Container PValue)
- rrpos :: Lens' c PPosition
- class HasLinkInformation c where
- linkInformation :: Lens' c LinkInformation
- linkPos :: Lens' c PPosition
- linkType :: Lens' c LinkType
- linkdst :: Lens' c RIdentifier
- linksrc :: Lens' c RIdentifier
- class HasResDefaults c where
- class HasResourceModifier c where
- resourceModifier :: Lens' c ResourceModifier
- rmDeclaration :: Lens' c PPosition
- rmModifierType :: Lens' c ModifierType
- rmMutation :: Lens' c (Resource -> InterpreterMonad Resource)
- rmResType :: Lens' c Text
- rmSearch :: Lens' c RSearchExpression
- rmType :: Lens' c ResourceCollectorType
- class HasDaemonMethods c where
- daemonMethods :: Lens' c DaemonMethods
- dCatalogStats :: Lens' c MStats
- dGetCatalog :: Lens' c (Text -> Facts -> IO (Either PrettyError (FinalCatalog, EdgeMap, FinalCatalog, [Resource])))
- dParserStats :: Lens' c MStats
- dTemplateStats :: Lens' c MStats
- class HasNativeTypeMethods c where
- class HasScopeInformation c where
- scopeInformation :: Lens' c ScopeInformation
- scopeContainer :: Lens' c CurContainer
- scopeDefaults :: Lens' c (Container ResDefaults)
- scopeExtraTags :: Lens' c (HashSet Text)
- scopeOverrides :: Lens' c (HashMap RIdentifier ResRefOverride)
- scopeParent :: Lens' c (Maybe Text)
- scopeVariables :: Lens' c (Container (Pair (Pair PValue PPosition) CurContainerDesc))
- class HasResource c where
- resource :: Lens' c Resource
- ralias :: Lens' c (HashSet Text)
- rattributes :: Lens' c (Container PValue)
- rid :: Lens' c RIdentifier
- rnode :: Lens' c Nodename
- rpos :: Lens' c PPosition
- rrelations :: Lens' c (HashMap RIdentifier (HashSet LinkType))
- rscope :: Lens' c [CurContainerDesc]
- rtags :: Lens' c (HashSet Text)
- rvirtuality :: Lens' c Virtuality
- class HasInterpreterState c where
- interpreterState :: Lens' c InterpreterState
- curPos :: Lens' c PPosition
- curScope :: Lens' c [CurContainerDesc]
- definedResources :: Lens' c (HashMap RIdentifier Resource)
- extraRelations :: Lens' c [LinkInformation]
- loadedClasses :: Lens' c (Container (Pair ClassIncludeType PPosition))
- nestedDeclarations :: Lens' c (HashMap (TopLevelType, Text) Statement)
- resMod :: Lens' c [ResourceModifier]
- scopes :: Lens' c (Container ScopeInformation)
- class HasInterpreterReader c m | c -> m where
- interpreterReader :: Lens' c (InterpreterReader m)
- computeTemplateFunction :: Lens' c (Either Text Text -> Text -> Container ScopeInformation -> m (Either PrettyError Text))
- externalFunctions :: Lens' c (Container ([PValue] -> InterpreterMonad PValue))
- getStatement :: Lens' c (TopLevelType -> Text -> m (Either PrettyError Statement))
- hieraQuery :: Lens' c (HieraQueryFunc m)
- ignoredModules :: Lens' c (HashSet Text)
- ioMethods :: Lens' c (ImpureMethods m)
- nativeTypes :: Lens' c (Container NativeTypeMethods)
- pdbAPI :: Lens' c (PuppetDBAPI m)
- thisNodename :: Lens' c Text
- class HasImpureMethods c m | c -> m where
- impureMethods :: Lens' c (ImpureMethods m)
- imCallLua :: Lens' c (MVar LuaState -> Text -> [PValue] -> m (Either String PValue))
- imGetCurrentCallStack :: Lens' c (m [String])
- imReadFile :: Lens' c ([Text] -> m (Either String Text))
- imTraceEvent :: Lens' c (String -> m ())
- class HasCurContainer c where
- curContainer :: Lens' c CurContainer
- cctags :: Lens' c (HashSet Text)
- cctype :: Lens' c CurContainerDesc
- class HasNodename s a | s -> a where
- class HasTransactionUUID s a | s -> a where
- transactionUUID :: Lens' s a
- class HasWEdges s a | s -> a where
- class HasWResources s a | s -> a where
- wResources :: Lens' s a
- class HasWVersion s a | s -> a where
- class HasFactname s a | s -> a where
- class HasFactval s a | s -> a where
- class HasCatalogT s a | s -> a where
- class HasDeactivated s a | s -> a where
- deactivated :: Lens' s a
- class HasFactsT s a | s -> a where
- class HasReportT s a | s -> a where
- rcurcontainer :: Resource -> CurContainerDesc
- class MonadThrowPos m where
- throwPosError :: Doc -> m a
- class MonadStack m where
- getCallStack :: m [String]
- getCurContainer :: InterpreterMonad CurContainer
- scopeName :: CurContainerDesc -> Text
- getScopeName :: InterpreterMonad Text
- getScope :: InterpreterMonad CurContainerDesc
- eitherDocIO :: IO (Either PrettyError a) -> IO (Either PrettyError a)
- interpreterIO :: (MonadThrowPos m, MonadIO m) => IO (Either PrettyError a) -> m a
- mightFail :: (MonadError PrettyError m, MonadThrowPos m) => m (Either PrettyError a) -> m a
- safeDecodeUtf8 :: ByteString -> InterpreterMonad Text
- interpreterError :: InterpreterMonad (Either PrettyError a) -> InterpreterMonad a
- resourceRelations :: Resource -> [(RIdentifier, LinkType)]
- ifromList :: (Monoid m, At m, Foldable f) => f (Index m, IxValue m) -> m
- ikeys :: (Eq k, Hashable k) => HashMap k v -> HashSet k
- isingleton :: (Monoid b, At b) => Index b -> IxValue b -> b
- ifromListWith :: (Monoid m, At m, Foldable f) => (IxValue m -> IxValue m -> IxValue m) -> f (Index m, IxValue m) -> m
- iinsertWith :: At m => (IxValue m -> IxValue m -> IxValue m) -> Index m -> IxValue m -> m -> m
- iunionWith :: (Hashable k, Eq k) => (v -> v -> v) -> HashMap k v -> HashMap k v -> HashMap k v
- fnull :: (Eq x, Monoid x) => x -> Bool
- rid2text :: RIdentifier -> Text
- text2Scientific :: Text -> Maybe Scientific
- initialState :: Facts -> InterpreterState
- dummypos :: PPosition
Documentation
newtype PrettyError Source
Constructors
| PrettyError | |
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 RSearchExpression Source
Constructors
| REqualitySearch !Text !PValue | |
| RNonEqualitySearch !Text !PValue | |
| RAndSearch !RSearchExpression !RSearchExpression | |
| ROrSearch !RSearchExpression !RSearchExpression | |
| RAlwaysTrue |
Instances
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. |
Instances
data ResDefaults Source
Constructors
| ResDefaults | |
Fields
| |
Instances
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 CurContainer Source
Constructors
| CurContainer | |
Fields
| |
Instances
data ScopeInformation Source
Constructors
| ScopeInformation | |
Fields
| |
Instances
data InterpreterState Source
Constructors
| InterpreterState | |
Fields
| |
data InterpreterReader m Source
Constructors
| InterpreterReader | |
Fields
| |
Instances
data ImpureMethods m Source
Constructors
| ImpureMethods | |
Fields
| |
Instances
data InterpreterInstr a where Source
Constructors
type InterpreterLog = Pair Priority Doc Source
type InterpreterWriter = [InterpreterLog] Source
warn :: (Monad m, MonadWriter InterpreterWriter m) => Doc -> m () Source
debug :: (Monad m, MonadWriter InterpreterWriter m) => Doc -> m () Source
logWriter :: (Monad m, MonadWriter InterpreterWriter m) => Priority -> Doc -> m () Source
type InterpreterMonad = ProgramT InterpreterInstr (State InterpreterState) Source
The main monad
data RIdentifier Source
Constructors
| RIdentifier | |
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 ResourceModifier Source
Constructors
| ResourceModifier | |
Fields
| |
data LinkInformation Source
Constructors
| LinkInformation | |
Fields
| |
type EdgeMap = HashMap RIdentifier [LinkInformation] Source
This is a fully resolved resource that will be used in the
FinalCatalog.
Constructors
| Resource | |
Fields
| |
type NativeTypeValidate = Resource -> Either PrettyError Resource Source
data NativeTypeMethods Source
Attributes (and providers) of a puppet resource type bundled with validation rules
Constructors
| NativeTypeMethods | |
Fields | |
Instances
type FinalCatalog = HashMap RIdentifier Resource Source
data DaemonMethods Source
Constructors
| DaemonMethods | |
Fields
| |
Instances
data WireCatalog Source
Constructors
| WireCatalog | |
Fields | |
Constructors
| PFactInfo | |
Fields
| |
Constructors
| PNodeInfo | |
Fields
| |
data PuppetDBAPI m Source
Constructors
Pretty straightforward way to define the various PuppetDB queries
Fields for the fact endpoint
Fields for the node endpoint
class HasRIdentifier c where Source
Minimal complete definition
Methods
Instances
class HasResRefOverride c where Source
Minimal complete definition
Methods
resRefOverride :: Lens' c ResRefOverride Source
rrid :: Lens' c RIdentifier Source
Instances
class HasLinkInformation c where Source
Minimal complete definition
Methods
linkInformation :: Lens' c LinkInformation Source
linkPos :: Lens' c PPosition Source
linkType :: Lens' c LinkType Source
linkdst :: Lens' c RIdentifier Source
linksrc :: Lens' c RIdentifier Source
Instances
class HasResDefaults c where Source
Minimal complete definition
Methods
resDefaults :: Lens' c ResDefaults Source
defPos :: Lens' c PPosition Source
defSrcScope :: Lens' c Text Source
Instances
class HasResourceModifier c where Source
Minimal complete definition
Methods
resourceModifier :: Lens' c ResourceModifier Source
rmDeclaration :: Lens' c PPosition Source
rmModifierType :: Lens' c ModifierType Source
rmMutation :: Lens' c (Resource -> InterpreterMonad Resource) Source
rmResType :: Lens' c Text Source
Instances
class HasDaemonMethods c where Source
Minimal complete definition
Methods
daemonMethods :: Lens' c DaemonMethods Source
dCatalogStats :: Lens' c MStats Source
dGetCatalog :: Lens' c (Text -> Facts -> IO (Either PrettyError (FinalCatalog, EdgeMap, FinalCatalog, [Resource]))) Source
dParserStats :: Lens' c MStats Source
dTemplateStats :: Lens' c MStats Source
Instances
class HasNativeTypeMethods c where Source
Minimal complete definition
Methods
nativeTypeMethods :: Lens' c NativeTypeMethods Source
puppetFields :: Lens' c (HashSet Text) Source
Instances
class HasScopeInformation c where Source
Minimal complete definition
Methods
scopeInformation :: Lens' c ScopeInformation Source
scopeContainer :: Lens' c CurContainer Source
scopeDefaults :: Lens' c (Container ResDefaults) Source
scopeExtraTags :: Lens' c (HashSet Text) Source
scopeOverrides :: Lens' c (HashMap RIdentifier ResRefOverride) Source
scopeParent :: Lens' c (Maybe Text) Source
scopeVariables :: Lens' c (Container (Pair (Pair PValue PPosition) CurContainerDesc)) Source
Instances
class HasResource c where Source
Minimal complete definition
Methods
resource :: Lens' c Resource Source
ralias :: Lens' c (HashSet Text) Source
rattributes :: Lens' c (Container PValue) Source
rid :: Lens' c RIdentifier Source
rnode :: Lens' c Nodename Source
rpos :: Lens' c PPosition Source
rrelations :: Lens' c (HashMap RIdentifier (HashSet LinkType)) Source
rscope :: Lens' c [CurContainerDesc] Source
rtags :: Lens' c (HashSet Text) Source
rvirtuality :: Lens' c Virtuality Source
Instances
class HasInterpreterState c where Source
Minimal complete definition
Methods
interpreterState :: Lens' c InterpreterState Source
curPos :: Lens' c PPosition Source
curScope :: Lens' c [CurContainerDesc] Source
definedResources :: Lens' c (HashMap RIdentifier Resource) Source
extraRelations :: Lens' c [LinkInformation] Source
loadedClasses :: Lens' c (Container (Pair ClassIncludeType PPosition)) Source
nestedDeclarations :: Lens' c (HashMap (TopLevelType, Text) Statement) Source
resMod :: Lens' c [ResourceModifier] Source
scopes :: Lens' c (Container ScopeInformation) Source
Instances
class HasInterpreterReader c m | c -> m where Source
Minimal complete definition
Methods
interpreterReader :: Lens' c (InterpreterReader m) Source
computeTemplateFunction :: Lens' c (Either Text Text -> Text -> Container ScopeInformation -> m (Either PrettyError Text)) Source
externalFunctions :: Lens' c (Container ([PValue] -> InterpreterMonad PValue)) Source
getStatement :: Lens' c (TopLevelType -> Text -> m (Either PrettyError Statement)) Source
hieraQuery :: Lens' c (HieraQueryFunc m) Source
ignoredModules :: Lens' c (HashSet Text) Source
ioMethods :: Lens' c (ImpureMethods m) Source
nativeTypes :: Lens' c (Container NativeTypeMethods) Source
pdbAPI :: Lens' c (PuppetDBAPI m) Source
thisNodename :: Lens' c Text Source
Instances
class HasImpureMethods c m | c -> m where Source
Minimal complete definition
Methods
impureMethods :: Lens' c (ImpureMethods m) Source
imCallLua :: Lens' c (MVar LuaState -> Text -> [PValue] -> m (Either String PValue)) Source
imGetCurrentCallStack :: Lens' c (m [String]) Source
imReadFile :: Lens' c ([Text] -> m (Either String Text)) Source
imTraceEvent :: Lens' c (String -> m ()) Source
Instances
class HasCurContainer c where Source
Minimal complete definition
Instances
class HasNodename s a | s -> a where Source
class HasTransactionUUID s a | s -> a where Source
Methods
transactionUUID :: Lens' s a Source
Instances
class HasWVersion s a | s -> a where Source
Instances
class HasFactname s a | s -> a where Source
Instances
class HasFactval s a | s -> a where Source
Instances
class HasCatalogT s a | s -> a where Source
Instances
class HasReportT s a | s -> a where Source
Instances
scopeName :: CurContainerDesc -> Text Source
eitherDocIO :: IO (Either PrettyError a) -> IO (Either PrettyError a) Source
interpreterIO :: (MonadThrowPos m, MonadIO m) => IO (Either PrettyError a) -> m a Source
mightFail :: (MonadError PrettyError m, MonadThrowPos m) => m (Either PrettyError a) -> m a Source
resourceRelations :: Resource -> [(RIdentifier, LinkType)] 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 ..
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
rid2text :: RIdentifier -> Text Source
text2Scientific :: Text -> Maybe Scientific Source