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

Safe HaskellNone
LanguageHaskell98

Puppet.Parser

Contents

Description

Parse puppet source code from text.

Synopsis

Runner

runPuppetParser :: String -> Text -> Either (ParseErrorBundle Text Void) (Vector Statement) Source #

Run a puppet parser against some Text input.

Parsers

puppetParser :: Parser (Vector Statement) Source #

Parse a collection of puppet Statement.

prettyParseError :: ParseErrorBundle Text Void -> PrettyError Source #

Build a PrettyError from a ParseError given the text source. The source is used to display the line on which the error occurs.

Pretty Print

ppStatements :: Vector Statement -> Doc Source #

Pretty print a series of statements.

Expressions

data Expression Source #

Instances
IsList Expression Source # 
Instance details

Defined in Puppet.Parser.Types

Associated Types

type Item Expression :: Type #

Eq Expression Source # 
Instance details

Defined in Puppet.Parser.Types

Fractional Expression Source # 
Instance details

Defined in Puppet.Parser.Types

Num Expression Source # 
Instance details

Defined in Puppet.Parser.Types

Show Expression Source # 
Instance details

Defined in Puppet.Parser.Types

IsString Expression Source # 
Instance details

Defined in Puppet.Parser.Types

Pretty Expression Source # 
Instance details

Defined in Puppet.Parser.PrettyPrinter

type Item Expression Source # 
Instance details

Defined in Puppet.Parser.Types

data UnresolvedValue Source #

An unresolved value, typically the parser's output.

Constructors

UBoolean !Bool

Special tokens generated when parsing the true or false literals.

UString !Text

Raw string.

UInterpolable !(Vector Expression)

A string that might contain variable references. The type should be refined at one point.

UUndef

Special token that is generated when parsing the undef literal.

UResourceReference !Text !Expression

Alike Resource[reference]

UArray !(Vector Expression) 
UHash !(Vector (Pair Expression Expression)) 
URegexp !CompRegex

The regular expression compilation is performed during parsing.

UVariableReference !Text 
UFunctionCall !Text !(Vector Expression) 
UHOLambdaCall !HOLambdaCall 
UNumber !Scientific 
UDataType UDataType 

newtype LambdaFunc Source #

High Order lambdas.

Constructors

LambdaFunc Text 
Instances
Eq LambdaFunc Source # 
Instance details

Defined in Puppet.Parser.Types

Show LambdaFunc Source # 
Instance details

Defined in Puppet.Parser.Types

Pretty LambdaFunc Source # 
Instance details

Defined in Puppet.Parser.PrettyPrinter

type LambdaParameters = Vector LambdaParameter Source #

Lambda block parameters:

data CollectorType Source #

Constructors

Collector

Single angle brackets <| |>

ExportedCollector

Double angle brackets <<| |>>

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 NodeDesc Source #

Instances
Eq NodeDesc Source # 
Instance details

Defined in Puppet.Parser.Types

Show NodeDesc Source # 
Instance details

Defined in Puppet.Parser.Types

Pretty NodeDesc Source # 
Instance details

Defined in Puppet.Parser.PrettyPrinter

Methods

pretty :: NodeDesc -> Doc #

prettyList :: [NodeDesc] -> Doc #

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)))

Synonyms

Datatypes

Search Expressions

Declaration

data ArrowOp Source #

Constructors

AppendArrow

+>

AssignArrow

`=>`

Instances
Eq ArrowOp Source # 
Instance details

Defined in Puppet.Parser.Types

Methods

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

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

Show ArrowOp Source # 
Instance details

Defined in Puppet.Parser.Types

Pretty ArrowOp Source # 
Instance details

Defined in Puppet.Parser.PrettyPrinter

Methods

pretty :: ArrowOp -> Doc #

prettyList :: [ArrowOp] -> Doc #

data ConditionalDecl Source #

All types of conditional statements : case, if, ...

Stored as an ordered list of pair (condition, statements) . Interpreted as "if first cond is true, choose first statements, else take the next pair, check the condition ..."

data ClassDecl Source #

Declare a class with

  • a name
  • a list of parameters
  • an optional inherits
  • a list of statements
  • a position
Instances
Eq ClassDecl Source # 
Instance details

Defined in Puppet.Parser.Types

Show ClassDecl Source # 
Instance details

Defined in Puppet.Parser.Types

data ResDefaultDecl Source #

Resource default:

 File { mode => 755 }

puppet reference.

data DepDecl Source #

Instances
Eq DepDecl Source # 
Instance details

Defined in Puppet.Parser.Types

Methods

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

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

Show DepDecl Source # 
Instance details

Defined in Puppet.Parser.Types

data ResDecl Source #

Resource declaration:

 file { mode => 755}
Instances
Eq ResDecl Source # 
Instance details

Defined in Puppet.Parser.Types

Methods

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

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

Show ResDecl Source # 
Instance details

Defined in Puppet.Parser.Types

data DefineDecl Source #

Declare a define with * a name * a list of parameters * a list of statements * a position

Instances
Eq DefineDecl Source # 
Instance details

Defined in Puppet.Parser.Types

Show DefineDecl Source # 
Instance details

Defined in Puppet.Parser.Types

data NodeDecl Source #

A node is a collection of statements + maybe an inherit node.

Instances
Eq NodeDecl Source # 
Instance details

Defined in Puppet.Parser.Types

Show NodeDecl Source # 
Instance details

Defined in Puppet.Parser.Types

data ResCollDecl Source #

Resource Collector including exported collector (`<<| |>>`)

 User <| title == jenkins |> { groups +> "docker"}

See puppet reference

Instances
Eq ResCollDecl Source # 
Instance details

Defined in Puppet.Parser.Types

Show ResCollDecl Source # 
Instance details

Defined in Puppet.Parser.Types

Prism for Statements

Prism for Expressions