| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Puppet.Parser
Contents
Description
Parse puppet source code from text.
Synopsis
- runPuppetParser :: String -> Text -> Either (ParseErrorBundle Text Void) (Vector Statement)
- puppetParser :: Parser (Vector Statement)
- prettyParseError :: ParseErrorBundle Text Void -> PrettyError
- ppStatements :: Vector Statement -> Doc
- data Expression
- = Equal !Expression !Expression
- | Different !Expression !Expression
- | Not !Expression
- | And !Expression !Expression
- | Or !Expression !Expression
- | LessThan !Expression !Expression
- | MoreThan !Expression !Expression
- | LessEqualThan !Expression !Expression
- | MoreEqualThan !Expression !Expression
- | RegexMatch !Expression !Expression
- | NotRegexMatch !Expression !Expression
- | Contains !Expression !Expression
- | Addition !Expression !Expression
- | Substraction !Expression !Expression
- | Division !Expression !Expression
- | Multiplication !Expression !Expression
- | Modulo !Expression !Expression
- | RightShift !Expression !Expression
- | LeftShift !Expression !Expression
- | Lookup !Expression !Expression
- | Negate !Expression
- | ConditionalValue !Expression !(Vector (Pair SelectorCase Expression))
- | FunctionApplication !Expression !Expression
- | Terminal !UnresolvedValue
- data SelectorCase
- data UnresolvedValue
- = UBoolean !Bool
- | UString !Text
- | UInterpolable !(Vector Expression)
- | UUndef
- | UResourceReference !Text !Expression
- | UArray !(Vector Expression)
- | UHash !(Vector (Pair Expression Expression))
- | URegexp !CompRegex
- | UVariableReference !Text
- | UFunctionCall !Text !(Vector Expression)
- | UHOLambdaCall !HOLambdaCall
- | UNumber !Scientific
- | UDataType UDataType
- newtype LambdaFunc = LambdaFunc Text
- data HOLambdaCall = HOLambdaCall {}
- data ChainableRes
- class HasHOLambdaCall c where
- data LambdaParameter = LambdaParam !(Maybe UDataType) !Text
- type LambdaParameters = Vector LambdaParameter
- data CompRegex = CompRegex !Text !Regex
- data CollectorType
- data Virtuality
- data NodeDesc
- data LinkType
- = RRequire
- | RBefore
- | RNotify
- | RSubscribe
- type Parser = Parsec Void Text
- type PuppetParseError = ParseError Char Void
- data UDataType
- = UDTType
- | UDTString (Maybe Int) (Maybe Int)
- | UDTInteger (Maybe Int) (Maybe Int)
- | UDTFloat (Maybe Double) (Maybe Double)
- | UDTBoolean
- | UDTArray UDataType Int (Maybe Int)
- | UDTHash UDataType UDataType Int (Maybe Int)
- | UDTUndef
- | UDTScalar
- | UDTData
- | UDTOptional UDataType
- | UNotUndef
- | UDTVariant (NonEmpty UDataType)
- | UDTPattern (NonEmpty CompRegex)
- | UDTEnum (NonEmpty Expression)
- | UDTAny
- | UDTCollection
- | UDTRegexp (Maybe CompRegex)
- data SearchExpression
- data AttributeDecl
- data ArrowOp
- data ConditionalDecl = ConditionalDecl !(Vector (Pair Expression (Vector Statement))) !PPosition
- data ClassDecl = ClassDecl !Text !Parameters !(Maybe Text) !(Vector Statement) !PPosition
- data ResDefaultDecl = ResDefaultDecl !Text !(Vector AttributeDecl) !PPosition
- data DepDecl = DepDecl !(Pair Text Expression) !(Pair Text Expression) !LinkType !PPosition
- data Statement
- = ResourceDeclaration !ResDecl
- | ResourceDefaultDeclaration !ResDefaultDecl
- | ResourceOverrideDeclaration !ResOverrideDecl
- | ResourceCollectionDeclaration !ResCollDecl
- | ClassDeclaration !ClassDecl
- | DefineDeclaration !DefineDecl
- | NodeDeclaration !NodeDecl
- | ConditionalDeclaration !ConditionalDecl
- | VarAssignmentDeclaration !VarAssignDecl
- | MainFunctionDeclaration !MainFuncDecl
- | HigherOrderLambdaDeclaration !HigherOrderLambdaDecl
- | DependencyDeclaration !DepDecl
- | TopContainer !(Vector Statement) !Statement
- data ResDecl = ResDecl !Text !Expression !(Vector AttributeDecl) !Virtuality !PPosition
- data ResOverrideDecl = ResOverrideDecl !Text !Expression !(Vector AttributeDecl) !PPosition
- data DefineDecl = DefineDecl !Text !Parameters !(Vector Statement) !PPosition
- data NodeDecl = NodeDecl !NodeDesc !(Vector Statement) !(Maybe NodeDesc) !PPosition
- data VarAssignDecl = VarAssignDecl {}
- data MainFuncDecl = MainFuncDecl !Text !(Vector Expression) !PPosition
- data HigherOrderLambdaDecl = HigherOrderLambdaDecl !HOLambdaCall !PPosition
- data ResCollDecl = ResCollDecl !CollectorType !Text !SearchExpression !(Vector AttributeDecl) !PPosition
- type Parameters = Vector (Pair (Pair Text (Maybe UDataType)) (Maybe Expression))
- _Statements :: Lens' Statement [Statement]
- _ResDecl :: Prism' Statement ResDecl
- _ResDefaultDecl :: Prism' Statement ResDefaultDecl
- _ResOverrDecl :: Prism' Statement ResOverrideDecl
- _ResCollDecl :: Prism' Statement ResCollDecl
- _ConditionalDecl :: Prism' Statement ConditionalDecl
- _ClassDecl :: Prism' Statement ClassDecl
- _DefineDecl :: Prism' Statement DefineDecl
- _NodeDecl :: Prism' Statement NodeDecl
- _VarAssignDecl :: Prism' Statement VarAssignDecl
- _MainFuncDecl :: Prism' Statement MainFuncDecl
- _HigherOrderLambdaDecl :: Prism' Statement HigherOrderLambdaDecl
- _DepDecl :: Prism' Statement DepDecl
- _Equal :: Prism' Expression (Expression, Expression)
- _Different :: Prism' Expression (Expression, Expression)
- _Not :: Prism' Expression Expression
- _And :: Prism' Expression (Expression, Expression)
- _Or :: Prism' Expression (Expression, Expression)
- _LessThan :: Prism' Expression (Expression, Expression)
- _MoreThan :: Prism' Expression (Expression, Expression)
- _LessEqualThan :: Prism' Expression (Expression, Expression)
- _MoreEqualThan :: Prism' Expression (Expression, Expression)
- _RegexMatch :: Prism' Expression (Expression, Expression)
- _NotRegexMatch :: Prism' Expression (Expression, Expression)
- _Contains :: Prism' Expression (Expression, Expression)
- _Addition :: Prism' Expression (Expression, Expression)
- _Substraction :: Prism' Expression (Expression, Expression)
- _Division :: Prism' Expression (Expression, Expression)
- _Multiplication :: Prism' Expression (Expression, Expression)
- _Modulo :: Prism' Expression (Expression, Expression)
- _RightShift :: Prism' Expression (Expression, Expression)
- _LeftShift :: Prism' Expression (Expression, Expression)
- _Lookup :: Prism' Expression (Expression, Expression)
- _Negate :: Prism' Expression Expression
- _ConditionalValue :: Prism' Expression (Expression, Vector (Pair SelectorCase Expression))
- _FunctionApplication :: Prism' Expression (Expression, Expression)
- _Terminal :: Prism' Expression UnresolvedValue
Runner
runPuppetParser :: String -> Text -> Either (ParseErrorBundle Text Void) (Vector Statement) Source #
Run a puppet parser against some Text input.
Parsers
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
Expressions
data Expression Source #
The Expressions
Constructors
| Equal !Expression !Expression | |
| Different !Expression !Expression | |
| Not !Expression | |
| And !Expression !Expression | |
| Or !Expression !Expression | |
| LessThan !Expression !Expression | |
| MoreThan !Expression !Expression | |
| LessEqualThan !Expression !Expression | |
| MoreEqualThan !Expression !Expression | |
| RegexMatch !Expression !Expression | |
| NotRegexMatch !Expression !Expression | |
| Contains !Expression !Expression | |
| Addition !Expression !Expression | |
| Substraction !Expression !Expression | |
| Division !Expression !Expression | |
| Multiplication !Expression !Expression | |
| Modulo !Expression !Expression | |
| RightShift !Expression !Expression | |
| LeftShift !Expression !Expression | |
| Lookup !Expression !Expression | Hash lookup |
| Negate !Expression | |
| ConditionalValue !Expression !(Vector (Pair SelectorCase Expression)) | All conditionals are stored in this format. |
| FunctionApplication !Expression !Expression | This is for higher order functions. |
| Terminal !UnresolvedValue | Terminal object contains no expression |
Instances
data SelectorCase Source #
Constructors
| SelectorValue !UnresolvedValue | |
| SelectorType !UDataType | |
| SelectorDefault |
Instances
| Eq SelectorCase Source # | |
Defined in Puppet.Parser.Types | |
| Show SelectorCase Source # | |
Defined in Puppet.Parser.Types Methods showsPrec :: Int -> SelectorCase -> ShowS # show :: SelectorCase -> String # showList :: [SelectorCase] -> ShowS # | |
| Pretty SelectorCase # | |
Defined in Puppet.Parser.PrettyPrinter | |
data UnresolvedValue Source #
An unresolved value, typically the parser's output.
Constructors
| UBoolean !Bool | Special tokens generated when parsing the |
| 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 |
| UResourceReference !Text !Expression | Alike |
| 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 |
Instances
| IsList UnresolvedValue Source # | |
Defined in Puppet.Parser.Types Associated Types type Item UnresolvedValue :: * # Methods fromList :: [Item UnresolvedValue] -> UnresolvedValue # fromListN :: Int -> [Item UnresolvedValue] -> UnresolvedValue # toList :: UnresolvedValue -> [Item UnresolvedValue] # | |
| Eq UnresolvedValue Source # | |
Defined in Puppet.Parser.Types Methods (==) :: UnresolvedValue -> UnresolvedValue -> Bool # (/=) :: UnresolvedValue -> UnresolvedValue -> Bool # | |
| Show UnresolvedValue Source # | |
Defined in Puppet.Parser.Types Methods showsPrec :: Int -> UnresolvedValue -> ShowS # show :: UnresolvedValue -> String # showList :: [UnresolvedValue] -> ShowS # | |
| IsString UnresolvedValue Source # | |
Defined in Puppet.Parser.Types Methods fromString :: String -> UnresolvedValue # | |
| Pretty UnresolvedValue # | |
Defined in Puppet.Parser.PrettyPrinter | |
| type Item UnresolvedValue Source # | |
Defined in Puppet.Parser.Types | |
newtype LambdaFunc Source #
High Order lambdas.
Constructors
| LambdaFunc Text |
Instances
| Eq LambdaFunc Source # | |
Defined in Puppet.Parser.Types | |
| Show LambdaFunc Source # | |
Defined in Puppet.Parser.Types Methods showsPrec :: Int -> LambdaFunc -> ShowS # show :: LambdaFunc -> String # showList :: [LambdaFunc] -> ShowS # | |
| Pretty LambdaFunc # | |
Defined in Puppet.Parser.PrettyPrinter | |
data HOLambdaCall Source #
Constructors
| HOLambdaCall | |
Fields
| |
Instances
| Eq HOLambdaCall Source # | |
Defined in Puppet.Parser.Types | |
| Show HOLambdaCall Source # | |
Defined in Puppet.Parser.Types Methods showsPrec :: Int -> HOLambdaCall -> ShowS # show :: HOLambdaCall -> String # showList :: [HOLambdaCall] -> ShowS # | |
| Pretty HOLambdaCall # | |
Defined in Puppet.Parser.PrettyPrinter | |
| HasHOLambdaCall HOLambdaCall Source # | |
Defined in Puppet.Parser.Types Methods hOLambdaCall :: Lens' HOLambdaCall HOLambdaCall Source # hoLambdaExpr :: Lens' HOLambdaCall (Vector Expression) Source # hoLambdaFunc :: Lens' HOLambdaCall LambdaFunc Source # hoLambdaLastExpr :: Lens' HOLambdaCall (Maybe Expression) Source # hoLambdaParams :: Lens' HOLambdaCall LambdaParameters Source # hoLambdaStatements :: Lens' HOLambdaCall (Vector Statement) Source # | |
data ChainableRes Source #
Constructors
| ChainResColl !ResCollDecl | |
| ChainResDecl !ResDecl | |
| ChainResRefr !Text [Expression] !PPosition |
Instances
| Eq ChainableRes Source # | |
Defined in Puppet.Parser.Types | |
| Show ChainableRes Source # | |
Defined in Puppet.Parser.Types Methods showsPrec :: Int -> ChainableRes -> ShowS # show :: ChainableRes -> String # showList :: [ChainableRes] -> ShowS # | |
class HasHOLambdaCall c where Source #
Minimal complete definition
Methods
hOLambdaCall :: Lens' c HOLambdaCall Source #
hoLambdaExpr :: Lens' c (Vector Expression) Source #
hoLambdaFunc :: Lens' c LambdaFunc Source #
hoLambdaLastExpr :: Lens' c (Maybe Expression) Source #
Instances
data LambdaParameter Source #
Constructors
| LambdaParam !(Maybe UDataType) !Text |
Instances
| Eq LambdaParameter Source # | |
Defined in Puppet.Parser.Types Methods (==) :: LambdaParameter -> LambdaParameter -> Bool # (/=) :: LambdaParameter -> LambdaParameter -> Bool # | |
| Show LambdaParameter Source # | |
Defined in Puppet.Parser.Types Methods showsPrec :: Int -> LambdaParameter -> ShowS # show :: LambdaParameter -> String # showList :: [LambdaParameter] -> ShowS # | |
| Pretty LambdaParameters # | |
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 |
Instances
| Eq CollectorType Source # | |
Defined in Puppet.Parser.Types Methods (==) :: CollectorType -> CollectorType -> Bool # (/=) :: CollectorType -> CollectorType -> Bool # | |
| Show CollectorType Source # | |
Defined in Puppet.Parser.Types Methods showsPrec :: Int -> CollectorType -> ShowS # show :: CollectorType -> String # showList :: [CollectorType] -> ShowS # | |
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 # | |
Defined in Puppet.Language.Resource | |
| Show Virtuality Source # | |
Defined in Puppet.Language.Resource Methods showsPrec :: Int -> Virtuality -> ShowS # show :: Virtuality -> String # showList :: [Virtuality] -> ShowS # | |
Constructors
| NodeName !Text | |
| NodeMatch !CompRegex | |
| NodeDefault |
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 # | |
| Show LinkType Source # | |
| Generic LinkType Source # | |
| Hashable LinkType Source # | |
Defined in Puppet.Language.Resource | |
| ToJSON LinkType Source # | |
Defined in Puppet.Language.Resource | |
| FromJSON LinkType Source # | |
| Pretty LinkType Source # | |
Defined in Puppet.Language.Resource | |
| type Rep LinkType Source # | |
Defined in Puppet.Language.Resource type Rep LinkType = D1 (MetaData "LinkType" "Puppet.Language.Resource" "language-puppet-1.4.3-HDQJwfJDSsZ3qfCihzdt4N" False) ((C1 (MetaCons "RRequire" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "RBefore" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "RNotify" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "RSubscribe" PrefixI False) (U1 :: * -> *))) | |
Synonyms
type PuppetParseError = ParseError Char Void Source #
Datatypes
Constructors
Search Expressions
data SearchExpression Source #
Search expression inside collector <| searchexpr |>
Constructors
| EqualitySearch !Text !Expression | |
| NonEqualitySearch !Text !Expression | |
| AndSearch !SearchExpression !SearchExpression | |
| OrSearch !SearchExpression !SearchExpression | |
| AlwaysTrue |
Instances
| Eq SearchExpression Source # | |
Defined in Puppet.Parser.Types Methods (==) :: SearchExpression -> SearchExpression -> Bool # (/=) :: SearchExpression -> SearchExpression -> Bool # | |
| Show SearchExpression Source # | |
Defined in Puppet.Parser.Types Methods showsPrec :: Int -> SearchExpression -> ShowS # show :: SearchExpression -> String # showList :: [SearchExpression] -> ShowS # | |
| Pretty SearchExpression # | |
Defined in Puppet.Parser.PrettyPrinter | |
Declaration
data AttributeDecl Source #
Constructors
| AttributeDecl !Text !ArrowOp !Expression | |
| AttributeWildcard !Expression |
Instances
| Eq AttributeDecl Source # | |
Defined in Puppet.Parser.Types Methods (==) :: AttributeDecl -> AttributeDecl -> Bool # (/=) :: AttributeDecl -> AttributeDecl -> Bool # | |
| Show AttributeDecl Source # | |
Defined in Puppet.Parser.Types Methods showsPrec :: Int -> AttributeDecl -> ShowS # show :: AttributeDecl -> String # showList :: [AttributeDecl] -> ShowS # | |
Constructors
| AppendArrow |
|
| AssignArrow | `=>` |
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 ..."
Constructors
| ConditionalDecl !(Vector (Pair Expression (Vector Statement))) !PPosition |
Instances
| Eq ConditionalDecl Source # | |
Defined in Puppet.Parser.Types Methods (==) :: ConditionalDecl -> ConditionalDecl -> Bool # (/=) :: ConditionalDecl -> ConditionalDecl -> Bool # | |
| Show ConditionalDecl Source # | |
Defined in Puppet.Parser.Types Methods showsPrec :: Int -> ConditionalDecl -> ShowS # show :: ConditionalDecl -> String # showList :: [ConditionalDecl] -> ShowS # | |
Declare a class with
- a name
- a list of parameters
- an optional inherits
- a list of statements
- a position
data ResDefaultDecl Source #
Constructors
| ResDefaultDecl !Text !(Vector AttributeDecl) !PPosition |
Instances
| Eq ResDefaultDecl Source # | |
Defined in Puppet.Parser.Types Methods (==) :: ResDefaultDecl -> ResDefaultDecl -> Bool # (/=) :: ResDefaultDecl -> ResDefaultDecl -> Bool # | |
| Show ResDefaultDecl Source # | |
Defined in Puppet.Parser.Types Methods showsPrec :: Int -> ResDefaultDecl -> ShowS # show :: ResDefaultDecl -> String # showList :: [ResDefaultDecl] -> ShowS # | |
Constructors
| DepDecl !(Pair Text Expression) !(Pair Text Expression) !LinkType !PPosition |
All possible statements.
Constructors
| ResourceDeclaration !ResDecl | |
| ResourceDefaultDeclaration !ResDefaultDecl | |
| ResourceOverrideDeclaration !ResOverrideDecl | |
| ResourceCollectionDeclaration !ResCollDecl | |
| ClassDeclaration !ClassDecl | |
| DefineDeclaration !DefineDecl | |
| NodeDeclaration !NodeDecl | |
| ConditionalDeclaration !ConditionalDecl | |
| VarAssignmentDeclaration !VarAssignDecl | |
| MainFunctionDeclaration !MainFuncDecl | |
| HigherOrderLambdaDeclaration !HigherOrderLambdaDecl | |
| DependencyDeclaration !DepDecl | |
| TopContainer !(Vector Statement) !Statement | Special statement used to include the expressions that are top level. Certainly buggy, but probably just like the original implementation. |
Resource declaration:
file { mode => 755}Constructors
| ResDecl !Text !Expression !(Vector AttributeDecl) !Virtuality !PPosition |
data ResOverrideDecl Source #
Constructors
| ResOverrideDecl !Text !Expression !(Vector AttributeDecl) !PPosition |
Instances
| Eq ResOverrideDecl Source # | |
Defined in Puppet.Parser.Types Methods (==) :: ResOverrideDecl -> ResOverrideDecl -> Bool # (/=) :: ResOverrideDecl -> ResOverrideDecl -> Bool # | |
| Show ResOverrideDecl Source # | |
Defined in Puppet.Parser.Types Methods showsPrec :: Int -> ResOverrideDecl -> ShowS # show :: ResOverrideDecl -> String # showList :: [ResOverrideDecl] -> ShowS # | |
data DefineDecl Source #
Declare a define with * a name * a list of parameters * a list of statements * a position
Constructors
| DefineDecl !Text !Parameters !(Vector Statement) !PPosition |
Instances
| Eq DefineDecl Source # | |
Defined in Puppet.Parser.Types | |
| Show DefineDecl Source # | |
Defined in Puppet.Parser.Types Methods showsPrec :: Int -> DefineDecl -> ShowS # show :: DefineDecl -> String # showList :: [DefineDecl] -> ShowS # | |
A node is a collection of statements + maybe an inherit node.
data VarAssignDecl Source #
$newvar = worldConstructors
| VarAssignDecl | |
Instances
| Eq VarAssignDecl Source # | |
Defined in Puppet.Parser.Types Methods (==) :: VarAssignDecl -> VarAssignDecl -> Bool # (/=) :: VarAssignDecl -> VarAssignDecl -> Bool # | |
| Show VarAssignDecl Source # | |
Defined in Puppet.Parser.Types Methods showsPrec :: Int -> VarAssignDecl -> ShowS # show :: VarAssignDecl -> String # showList :: [VarAssignDecl] -> ShowS # | |
| Pretty VarAssignDecl # | |
Defined in Puppet.Parser.PrettyPrinter | |
data MainFuncDecl Source #
Constructors
| MainFuncDecl !Text !(Vector Expression) !PPosition |
Instances
| Eq MainFuncDecl Source # | |
Defined in Puppet.Parser.Types | |
| Show MainFuncDecl Source # | |
Defined in Puppet.Parser.Types Methods showsPrec :: Int -> MainFuncDecl -> ShowS # show :: MainFuncDecl -> String # showList :: [MainFuncDecl] -> ShowS # | |
data HigherOrderLambdaDecl Source #
Higher order function call.
Constructors
| HigherOrderLambdaDecl !HOLambdaCall !PPosition |
Instances
| Eq HigherOrderLambdaDecl Source # | |
Defined in Puppet.Parser.Types Methods (==) :: HigherOrderLambdaDecl -> HigherOrderLambdaDecl -> Bool # (/=) :: HigherOrderLambdaDecl -> HigherOrderLambdaDecl -> Bool # | |
| Show HigherOrderLambdaDecl Source # | |
Defined in Puppet.Parser.Types Methods showsPrec :: Int -> HigherOrderLambdaDecl -> ShowS # show :: HigherOrderLambdaDecl -> String # showList :: [HigherOrderLambdaDecl] -> ShowS # | |
data ResCollDecl Source #
Resource Collector including exported collector (`<<| |>>`)
User <| title == jenkins |> { groups +> "docker"}See puppet reference
Constructors
| ResCollDecl !CollectorType !Text !SearchExpression !(Vector AttributeDecl) !PPosition |
Instances
| Eq ResCollDecl Source # | |
Defined in Puppet.Parser.Types | |
| Show ResCollDecl Source # | |
Defined in Puppet.Parser.Types Methods showsPrec :: Int -> ResCollDecl -> ShowS # show :: ResCollDecl -> String # showList :: [ResCollDecl] -> ShowS # | |
Prism for Statements
Prism for Expressions
_And :: Prism' Expression (Expression, Expression) Source #
_Or :: Prism' Expression (Expression, Expression) Source #