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

Safe HaskellNone
LanguageHaskell98

Puppet.Language

Description

General puppet language specification.

This module doesn't depend on any other project modules (except for XPrelude). It serves as a common bridge that can be used in PuppetDB or Facter as well as in Puppet.Interpreter or Puppet.Parser.

Synopsis

Documentation

showPPos :: PPosition -> Doc Source #

showing the first position of a position interval.

showPPos' :: PPosition -> String Source #

showing the first position of a position interval as string.

initialPPos :: FilePath -> PPosition Source #

Generates an initial position interval based on a filename.

type PPosition = Pair Position Position Source #

A pair containing the start and end of a given token.

type Position = SourcePos Source #

Position in a puppet file. Currently an alias to SourcePos.

stringEscape :: Text -> Text Source #

Extremely hacky escaping system for text values.

capitalizeR :: Text -> Doc Source #

Capitalize resource type and convert into a Doc.

capitalizeRT :: Text -> Text Source #

Properly capitalizes resource types.

containerComma' :: Pretty a => [(Doc, a)] -> Doc Source #

toPPos :: Text -> Int -> PPosition Source #

Generates a PPosition based on a filename and line number.

data NativeTypeMethods Source #

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

data PuppetDirPaths Source #

Constructors

PuppetDirPaths 

Fields

data Resource Source #

A fully resolved puppet resource that will be used in the FinalCatalog.

Constructors

Resource 

Fields

data RIdentifier Source #

In Puppet, a resource is identified by a name and a type.

Constructors

RIdentifier 

Fields

Instances
Eq RIdentifier Source # 
Instance details

Defined in Puppet.Language.Resource

Ord RIdentifier Source # 
Instance details

Defined in Puppet.Language.Resource

Show RIdentifier Source # 
Instance details

Defined in Puppet.Language.Resource

Generic RIdentifier Source # 
Instance details

Defined in Puppet.Language.Resource

Associated Types

type Rep RIdentifier :: Type -> Type #

Hashable RIdentifier Source # 
Instance details

Defined in Puppet.Language.Resource

ToJSON RIdentifier Source # 
Instance details

Defined in Puppet.Language.Resource

FromJSON RIdentifier Source # 
Instance details

Defined in Puppet.Language.Resource

Pretty RIdentifier Source # 
Instance details

Defined in Puppet.Language.Resource

HasRIdentifier RIdentifier Source # 
Instance details

Defined in Puppet.Language.Resource

type Rep RIdentifier Source # 
Instance details

Defined in Puppet.Language.Resource

type Rep RIdentifier = D1 (MetaData "RIdentifier" "Puppet.Language.Resource" "language-puppet-1.4.4-14mWiAtdidG3lhf9lLUdY3" False) (C1 (MetaCons "RIdentifier" PrefixI True) (S1 (MetaSel (Just "_itype") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_iname") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

data LinkType Source #

Relationship/ordering between resources.

Constructors

RRequire

Applies a resource after the target resource.

RBefore

Applies a resource before the target resource.

RNotify

Applies a resource before the target resource. The target resource refreshes if the notifying resource changes.

RSubscribe

Applies a resource after the target resource. The subscribing resource refreshes if the target resource changes.

Instances
Eq LinkType Source # 
Instance details

Defined in Puppet.Language.Resource

Show LinkType Source # 
Instance details

Defined in Puppet.Language.Resource

Generic LinkType Source # 
Instance details

Defined in Puppet.Language.Resource

Associated Types

type Rep LinkType :: Type -> Type #

Methods

from :: LinkType -> Rep LinkType x #

to :: Rep LinkType x -> LinkType #

Hashable LinkType Source # 
Instance details

Defined in Puppet.Language.Resource

Methods

hashWithSalt :: Int -> LinkType -> Int #

hash :: LinkType -> Int #

ToJSON LinkType Source # 
Instance details

Defined in Puppet.Language.Resource

FromJSON LinkType Source # 
Instance details

Defined in Puppet.Language.Resource

Pretty LinkType Source # 
Instance details

Defined in Puppet.Language.Resource

Methods

pretty :: LinkType -> Doc #

prettyList :: [LinkType] -> Doc #

type Rep LinkType Source # 
Instance details

Defined in Puppet.Language.Resource

type Rep LinkType = D1 (MetaData "LinkType" "Puppet.Language.Resource" "language-puppet-1.4.4-14mWiAtdidG3lhf9lLUdY3" False) ((C1 (MetaCons "RRequire" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RBefore" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "RNotify" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RSubscribe" PrefixI False) (U1 :: Type -> Type)))

data Virtuality Source #

Constructors

Normal

Normal resource, that will be included in the catalog.

Virtual

Type for virtual resources.

Exported

Type for exported resources.

ExportedRealized

These are resources that are exported AND realized in the catalog.

Instances
Eq Virtuality Source # 
Instance details

Defined in Puppet.Language.Resource

Show Virtuality Source # 
Instance details

Defined in Puppet.Language.Resource

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

Instances
Eq CurContainerDesc Source # 
Instance details

Defined in Puppet.Language.Resource

Ord CurContainerDesc Source # 
Instance details

Defined in Puppet.Language.Resource

Show CurContainerDesc Source # 
Instance details

Defined in Puppet.Language.Resource

Generic CurContainerDesc Source # 
Instance details

Defined in Puppet.Language.Resource

Associated Types

type Rep CurContainerDesc :: Type -> Type #

Pretty CurContainerDesc Source # 
Instance details

Defined in Puppet.Language.Resource

type Rep CurContainerDesc Source # 
Instance details

Defined in Puppet.Language.Resource

data PValue Source #

A puppet value.

Instances
Eq PValue Source # 
Instance details

Defined in Puppet.Language.Value

Methods

(==) :: PValue -> PValue -> Bool #

(/=) :: PValue -> PValue -> Bool #

Show PValue Source # 
Instance details

Defined in Puppet.Language.Value

IsString PValue Source # 
Instance details

Defined in Puppet.Language.Value

Methods

fromString :: String -> PValue #

ToJSON PValue Source # 
Instance details

Defined in Puppet.Language.Value

FromJSON PValue Source # 
Instance details

Defined in Puppet.Language.Value

Pretty PValue Source # 
Instance details

Defined in Puppet.Language.Value

Methods

pretty :: PValue -> Doc #

prettyList :: [PValue] -> Doc #

FromRuby PValue Source # 
Instance details

Defined in Puppet.Language.Value

ToRuby PValue Source # 
Instance details

Defined in Puppet.Language.Value

Methods

toRuby :: PValue -> IO RValue #

AsNumber PValue Source # 
Instance details

Defined in Puppet.Language.Value

Pretty (HashMap Text PValue) Source # 
Instance details

Defined in Puppet.Language.Value