stan-0.0.1.0: Haskell STatic ANalyser
Copyright(c) 2020 Kowainik
LicenseMPL-2.0
MaintainerKowainik <xrom.xkov@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Stan.Pattern.Ast

Description

Patterns for AST and syntax tree nodes search.

Synopsis

Type

data PatternAst Source #

Query pattern used to search AST nodes in HIE AST. This data type tries to mirror HIE AST to each future matching, so it's quite low-level, but helper functions are provided.

Constructors

PatternAstConstant !Literal

Integer constant in code.

PatternAstName !NameMeta !PatternType

Name of a specific function, variable or data type.

PatternAstVarName !String

Variable name.

PatternAstNode !(Set (FastString, FastString))

Set of context info (pairs of tags) | AST node with tags for current node and children patterns. This pattern should match the node exactly.

PatternAstNodeExact 

Fields

PatternAstAnything 
PatternAstOr !PatternAst !PatternAst

Choice between patterns. Should match either of them.

PatternAstAnd !PatternAst !PatternAst

Union of patterns. Should match both of them.

PatternAstNeg !PatternAst

Negation of pattern. Should match everything except this pattern.

PatternAstIdentifierDetailsDecl !DeclType

AST node with the specified Identifier details (only DeclType)

data Literal Source #

Instances

Instances details
Eq Literal Source # 
Instance details

Defined in Stan.Pattern.Ast

Methods

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

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

Show Literal Source # 
Instance details

Defined in Stan.Pattern.Ast

Helpers

namesToPatternAst :: NonEmpty (NameMeta, PatternType) -> PatternAst Source #

Function that creates PatternAst from the given non-empty list of pairs NameMeta and PatternType.

If the list contains only one PatternType then it is simple PatternAstName. Else it is PatternAstOr of all such PatternAstNames.

eDSL

app :: PatternAst -> PatternAst -> PatternAst Source #

app f x is a pattern for function application f x.

opApp :: PatternAst -> PatternAst -> PatternAst -> PatternAst Source #

opApp x op y is a pattern for operator application x op y.

constructor :: PatternAst Source #

Constructor of a plain data type or newtype. Children of node that matches this pattern are constructor fields.

constructorNameIdentifier :: PatternAst Source #

Constructor name Identifier info

dataDecl :: PatternAst Source #

data or newtype declaration.

fixity :: PatternAst Source #

Pattern for the top-level fixity declaration:

infixr 7 ***, +++, ???

fun :: PatternAst Source #

Pattern for the function definition:

foo x y = ...

guardBranch :: PatternAst Source #

Pattern for a single guard branch:

    | x < y = ...

lazyField :: PatternAst Source #

Lazy data type field. Comes in two shapes:

  1. Record field, like: foo :: Text
  2. Simple type: Int

range :: PatternAst -> PatternAst -> PatternAst Source #

range a b is a pattern for [a .. b]

rhs :: PatternAst Source #

Pattern for the right-hand-side. Usually an equality sign.

   foo = baz

tuple :: PatternAst Source #

Pattern for tuples:

  • Type signatures: foo :: (Int, Int, Int, Int)
  • Literals: (True, 0, [], Nothing)

typeSig :: PatternAst Source #

Pattern for the function type signature declaration:

foo :: Some -> Type

Pattern matching

case' :: PatternAst Source #

case' is a pattern for case EXP of expression (not considering branches).

lambdaCase :: PatternAst Source #

lambdaCase is a pattern for case expression (not considering branches).

patternMatchBranch :: PatternAst Source #

Pattern to represent one pattern matching branch.

patternMatchArrow :: PatternAst -> PatternAst Source #

Pattern to represent right side of the pattern matching, e.g. -> "foo".

patternMatch_ :: PatternAst -> PatternAst Source #

Pattern to represent one pattern matching branch on _.

literalPat :: PatternAst Source #

Pattern for literals in pattern matching.

Note: presents on GHC >=8.10 only.

wildPat :: PatternAst Source #

Pattern for _ in pattern matching.

Note: presents on GHC >=8.10 only.

More low-level interface

literalAnns :: (FastString, FastString) Source #

Annotations for constants: 0, "foo", etc.