5. LKQL Language Reference

LKQL (short for LangKit Query Language) is a query language enabling users to run queries on top of source code.

LKQL today is the mixture of two language subsets:

  • The first is a dynamically typed, functional, small but general purpose programming language, including function definitions, common expressions, very basic support for numeric types and computations, list comprehensions, etc.

  • The second is a tree query language, allowing the user to express very concisely predicates over a node and its syntactic and semantic relatives, and tree traversal logics.

Those two subsets will be documented separately. The general language will be documented first, because its knowledge is needed for understanding the tree query language.

LKQL is based upon the langkit technology. As such, it is theoretically capable of running queries on any language with a Langkit frontend. In practice for the moment, LKQL is hardwired for Ada (and Libadalang).

Attention

While mostly stable, LKQL is not completely done yet. The language will keep being extended with new constructs, and from time to time syntax might change to accommodate new language constructs/enhance the language ergonomics/fix design mistakes. Read the Language Changes section for more information.

5.1. General Purpose Language Subset

This language subset is composed of a reduced set of declarations and expressions that forms a minimal but turing complete language.

For the time being, it has no side effects, which is intended since the purpose of LKQL is strictly to express queries.

5.1.1. Data Types

LKQL has a very limited number of data types for the moment. Here are the current data types:

5.1.1.1. Basic Data Types

Unit

A type used to represents empty values.

Int

Basic integer type, supporting arbitrary sized values. Supports simple arithmetic.

Str

Built-in string type, that supports concatenation.

Bool

Built-in boolean type, that supports the usual expected boolean relational operators.

Node

Coming from the queried language (in the common case, Ada). Nodes correspond to the syntax nodes of the source files being queried. They can be explored as part of the general language subset, through Field access, or via the Query language subset.

Token

Also coming from the queried language. Tokens correspond to lexical units of the queried source files.

Pattern

Values of this type are compiled regular expressions that can be used in a few contexts to match a string against, notably in the string built-in functions contains and find.

Function

LKQL functions are first class citizens, thus, any expression can has this type which represents values that can be called with a call expression.

5.1.1.2. Composite Data Types

Tuple

Tuples are heterogeneous groups of values with a fixed size. They can be indexed to access inner values, a bit like Python tuples.

Attention

Tuples are indexed starting from 1, like in Lua/R/.., unlike in Python/Java/..

List

Lists are contiguous immutable sequences of items that can be indexed. Lists also support concatenation.

Attention

Like tuples, Lists are indexed starting from 1.

Object

Objects are heterogeneous records that can contain any number of key to value mappings, where keys are labels and values are any valid LKQL value.

5.1.2. Declarations

Declarations in LKQL only belong at the top level. There is no support currently for nested declarations, except in the block expression.

5.1.2.1. Function Declaration

fun_decl decl_annotation 'fun' id '(' param ',' ')' '=' doc_node expr param id ':' id '=' expr

Allows the user to declare an LKQL function that can be used to factor some computation:

fun add(x, y) = x + y

The syntax is simple, you only declare argument names and an expression after the =.

If you need to declare temporary named values in the body of your function, you can use a block expression:

fun add(x, y) = {
    |" Add two integers
    val ret = x + y;
    ret
}

Note

A function can have annotations. For the moment, this is used only in the context of LKQL checkers:

@check(message="Bla detected")
fun is_bla() = node is Bla

Functions can also be nested in other functions, and closures are allowed, ie. you can return a function that references the environment in which it was declared:

fun make_closure(closure_var) = {
    fun use_closure() = closure_var + 1;
    use_closure
}

# This will display the functional value "use_closure"
print(make_closure(12))

Note

Functions can be memoized via the @memoized annotation. In a language such as lkql that is purely functional, this will give a way for users to express/optimize computationally expensive things. Here is a simple example:

@memoized
fun fib(a) =
    if a == 0 then 0
    else (if a == 1 then 1
          else fib(a - 1) + fib (a - 2))

print(fib(30))

5.1.2.2. Value Declaration

val_decl decl_annotation doc_node 'val' id '=' expr

Declare a named value (often called a variable or constant in other languages):

val a = 12 + 15

Note that the value is immutable.

5.1.2.3. Docstrings

Declarations can have assorted docstrings. They’re part of the AST and are directly attached to the declaration:

# Docstrings

fun make_closure(closure_var) =
|" Make a function that will capture ``closure_var`` and return the sum of
|" it plus its first argument
{
    fun use_closure(x) = closure_var + x;
    use_closure
}

|" Function that will add 12 to its first argument
val adder = make_closure(12)

print(make_closure(12))

5.1.3. Expressions

5.1.3.1. Block Expression

block_expr '{' decl ';' expr ';' expr '}'

The block expression is useful to declare temporary named values and execute intermediate expressions. This can be useful to share the result of a temporary calculation, to name an intermediate value to make the code more readable, or to print debug values:

{
    val x = 40;
    val y = 2;
    print("DEBUG : " & (x + y).img);
    x + y
}

As you can see in the example above, value declarations and intermediate expressions are ended by semicolons. After the last one, you write the block’s result expression, without an ending semicolon.

5.1.3.2. Field Access

A field access returns the contents of a field. In the following example, we get the content of the f_type_expr syntax field on a node of type ObjectDecl:

object_decl.f_type_expr

A regular field access on a nullable variable is illegal and leads to a runtime error, which is why field access has a variant, which is called a “safe access”:

object_decl?.f_type_expr

The safe access will return null if the left hand side is null. This allows users to chain accesses without having to checks for nulls at every step.

In the context of rewriting features usage, you may want to get a reference to a field of a node. You can access such references with a dot-access notation on node kinds:

val ref_to_f_child = MyNodeKind.f_child

Such values can be used when calling RewritingContext’s methods.

5.1.3.3. Unwrap Expression

When you have a nullable object and you want to make it non nullable, you can use the unwrap expression. This is useful after a chain of safe accesses/calls, for example:

object_decl?.p_type_expr()?.p_designated_type_decl()!!

Unwrap will raise an error if the value is null.

5.1.3.4. Call Expression

fun_call id '?' '(' arg_list ')'

LKQL values of the Function type can be invoked with the call expression:

fun add(a, b) = a + b

val c = add(12, 15)
val d = add(a=12, b=15)

Parameters can be passed via positional or named associations.

Calls have a “safe” variant, that will return null if the callee is null:

fun add(a, b) = a + b
val fn = if true then null else add
fn?(1, 2) # Returns null

Additionally, you can also call selectors via the call syntax. Selector calls take only one argument, which is the starting point of the selector call chain:

children(select first AdaNode)

5.1.3.5. Constructor call

constructor_call 'new' upper_id '(' arg ',' ')'

You can call node constructors to create new nodes possibly used for the tree rewriting layer of LKQL. The result of a constructor call is a value of the RewritingNode type.

val token_node = new BooleanLiteral("Hello!")
val list_node = new SomeListNode(child_1, child_2)
val composite_node = new CompositeNode(
    f_child_1=token_node,
    f_child_2=list_node
)

As function calls, you can pass arguments via positional or named associations for composite nodes. About token and list nodes, you may only pass arguments through the positional format.

To know whether a node is a token, list or composite one, you may refer to the Langkit specification of the language you’re querying.

5.1.3.6. Indexing Expression

Indexing expression allows the user to access elements of a Tuple, List, LazyList, or Node.

When using the indexing expression on a node value:

  • for list nodes, it will access the different elements of the list

  • for regular nodes, it will access children in lexical order

Here are some examples of indexing expressions:

# Indexing a tuple
(1, 2, 3)[1]

# Indexing a list
list[1]

# Indexing a node with an arbitrary index
{
    val x = 2;
    node[x]
}

Indexing also has a safe variant, that will return unit instead of raising when an out of bound access is done:

val lst = [1, 2, 3]

# This will display "()"
print(lst?[5])

5.1.3.7. Comparison Expression

comp_expr comp_expr 'is' pattern comp_expr 'in' expr comp_expr '==' '!=' '<' '<=' '>' '>=' plus_expr plus_expr

Comparison expressions are used to compare an object to another object, or pattern. All those constructions are evaluated as booleans.

5.1.3.7.1. Membership Expression

The membership expression verifies that a collection (List/LazyList) contains the given value:

12 in list
5.1.3.7.2. Is Expression

The is expression verifies if a value matches a given pattern:

val a = select AdaNode
val b = a[1] is ObjectDecl
5.1.3.7.3. Comparison Operators

The usual comparison operators are available:

12 < 15
a == b
b != c

Order dependent operators (</>/…) are only usable on integers.

5.1.3.8. Object Literal

objectlit '{' object_assoc ',' '}'

An object literal is a literal representation of an object value:

# Object literal
{a: 1, b: "foo", c: null, d: [1, 2, 3, 4]}
at_object_lit '@' '{' at_object_assoc ',' '}'

“@” object literals are quite the same as standard objects literals, but each associated value is wrapped in a list (if not already one). You are also allowed to omit the associated expression when adding a key in the object. The default associated value is a list with only one element: an empty object.

# @-object literal
@{a: "Hello", b, c: 42, d}

# Is similar to
{a: ["Hello"], b: [{}], c: [42], d: [{}]}

This “@” object notation are mainly used to express coding standards in LKQL rule configuration files, however, you can use it in any context.

Object keys may contain upper-case characters at declaration, but the LKQL engine will lower them. This means that object keys are case-insensitive:

val o = {lower: "Hello", UPPER: "World"}

# This will display "Hello World"
print(o.lower & " " & o.upper)

Please note that objects are immutable.

5.1.3.9. List Literal

listlit '[' expr ',' ']'

A list literal is simply a literal representation of a list:

# Simple list literal
[1, 2, 3, 4]

Lists being immutable, lists literals are the primary way to create new lists from nothing, with list comprehension being the way to create new lists from existing lists.

5.1.3.10. List Comprehension

listcomp '[' expr 'for' id 'in' expr ',' 'if' expr ']'

A list comprehension allows the user to create a new list by iterating on an existing collection, applying a mapping operation, and eventually a filtering logic:

# Simple list comprehension that'll double every number in int_list if it
# is prime
[a * 2 for a in int_list if is_prime(a)]

# Complex example interleaving two collections
val subtypes = select SubtypeIndication
val objects = select ObjectDecl
print(
    [
        o.image & " " & st.image
        for o in objects, st in subtypes
        if (o.image & " " & st.image).length != 64
    ].to_list
)

A list comprehension is a basic language construct, that, since LKQL is purely functional, replaces traditional for loops. A list comprehension expression returns a value of the LazyList type, meaning that elements in the result aren’t computed until queried:

val lazy = [a * 2 for a in int_list if is_prime(a)]

# This will display "LazyList"
print(lazy)

# To display all elements of a lazy list, you have to convert it to a list
print(lazy.to_list)

5.1.3.11. If Expression

if_then_else 'if' expr 'then' expr 'else' expr

If expressions are traditional conditional expressions composed of a condition, an expression executed when the condition is true, and and expression executed when the condition is false:

# No parentheses required
val x = if b < 12 then c() else d()

The else branch is optional and its default value is true, this can be useful to express an implication logic:

# Without "else" expression
val y = if b < 12 then a == 0

5.1.3.12. Match Expression

match_expr 'match' expr match_arm

This expression is a pattern matching expression, and reuses the same patterns as the query part of the language. Matchers will be evaluated in order against the match’s target expression. The first matcher to match the object will trigger the evaluation of the associated expression in the match arm:

match nodes[1]
| ObjectDecl(p_has_aliased(): aliased @ *) => aliased
| ParamSpec(p_has_aliased(): aliased @ *) => aliased
| * => false

Note

For the moment, there is no static check that the matcher is complete. A match expression where no arm has matched will raise an exception at runtime.

5.1.3.13. Tuple Literal

tuple_expr '(' expr ',' ')'

The tuple literal is used to create a value of the Tuple composite type:

val t = (1, 2)
val tt = ("hello", "world")
val ttt = (t[1], tt[1])
print(t)
print(tt)
print(ttt)

Tuples are useful as function return values, or to aggregate data, since LKQL doesn’t have structs yet.

5.1.3.14. Anonymous Function

anonymous_function '(' param ',' ')' '=>' expr

LKQL supports first class functions, and anonymous functions expressions (or lambdas). Thus, you can create anonymous functional values:

fun mul_y(y) = (x) => x * y
val mul_2 = mul_y (2)
val four = mul_2 (2)

5.1.3.15. Literals and Operators

LKQL has literals for booleans, integers, strings, unit, and null values:

val a = true     # Boolean
val b = 12       # Integer
val c = "hello"  # String
val d = ()       # Unit
val e = null     # Null

Note

The LKQL null literal is used to represent a null node value, thus, it is different from the () (unit) value.

LKQL has multi-line string literals, called block-strings but they’re a bit different than in Python or other languages:

val a = |" Hello
        |" This is a multi line string
        |" Bue

Note

The first character after the " should be a whitespace. This is not enforced at parse-time but at run-time, so |"hello is still a syntactically valid block-string, but will raise an error when evaluated.

LKQL has a few built-in operators available:

  • Basic arithmetic operators on integers

val calc = a + 2 * 3 / 4 == b
val smaller_or_eq = a <= b
val greater_or_eq = b >= c
  • Basic relational operators on booleans

true and false or (a == b) and (not c)
  • Value concatenation

# Strings concatenation
"Hello " & name
# Lists concatenation
[1, 2, 3] & [4, 5, 6]

5.1.3.16. Module Importation

LKQL has a very simple module system. Basically every file in LKQL is a module, and you can import modules from other files with the import clause. When importing a module, you are associating its name to the namespace produced by the evaluation of its source (all declarations in its top-level):

# foo.lkql
fun bar() = 12

# bar.lkql
import foo

print(foo.bar())

LKQL will search for files:

  1. That are in the same directory as the current file

  2. That are in the LKQL_PATH environment variable

In case of multiple LKQL modules with the same name (two LKQL files named the same), an error is raised by the interpreter.

Note

There is no way to create hierarchies of modules for now, only flat modules are supported.

Attention

Circular dependencies are forbidden, thus the following files will raise an error at runtime:

# foo.lkql
import bar

# bar.lkql
import foo

Attention

In case of an ambiguous importation, the LKQL engine will raise a runtime error. For example, the following example will raise an error if the subdir directory is in the LKQL_PATH environment variable:

# foo.lkql
val x = 42

# subdir/foo.lkql
val y = 50

# bar.lkql
import foo
print(foo.x)

5.2. Query Language Subset

The query language subset is mainly composed of three language constructs: patterns, queries and selectors.

Patterns allow the user to express filtering logic on trees and graphs, akin to what regular expressions allow for strings.

A lot of the ideas behind patterns are similar to ideas in XPath, or even in CSS selectors

However, unlike in CSS or xpath, a pattern is just the filtering logic, not the traversal, even though filtering might contain sub traversals via selectors.

Here is a very simple example of a query expression, that will select object declarations that have the aliased qualifier:

# Queries are expressions, so their result can be stored in a named value
val a = select ObjectDecl(p_has_aliased(): true)

This will query every source file in the LKQL context, filter their nodes according to the provided pattern, and return the List containing all nodes matching the pattern.

Finally, selectors are a way to express “traversal” logic on the node graph. Syntactic nodes, when explored through their syntactic children, form a tree. However:

  • There are different ways to traverse this tree (for example, you can explore the parents starting from a node)

  • There are non syntactic ways to explore nodes, for example using semantic properties such as going from references to their declarations, or going up the tree of base types for a given tagged type.

All those traversals, including the most simple built-in one, use what is called selectors in LKQL. Those are a way to specify a traversal, which will return a LazyList of nodes as a result. Here is an example of a selector that will go up the parent chain:

selector parent
| AdaNode => rec(*this.parent, this)
| *       => ()

Read the Selector Declaration section for more information about selectors.

5.2.1. Query Expression

query 'from' '*' expr 'through' expr 'select' Identifier pattern 'through' expr 'select' Identifier pattern

The query expression is extremely simple, and most of the complexity lies in the upcoming sections about patterns.

A query traverses one or several trees, from one or several root nodes, applying the pattern on every node, and then returns a List containing all nodes that matched the pattern:

# Will select all non null nodes
select AdaNode

By default the query’s roots are implicit and set by the context. However, you can specify them with the from keyword, followed either by a Node value, or a List of nodes:

# Select all non null nodes starting from node a
from a select AdaNode

# Select all non null nodes starting from all nodes in list
from [a, b, c] select AdaNode

You can also run a query that will only select the first element, this can be useful to avoid visiting all the parsing tree:

# Select first basic declaration
select first BasicDecl

5.2.1.1. Specifying the selector

By default, queries traverse the syntactic tree from the root node to leaves. This behavior is equivalent to going through the nodes returned via the children built-in selector (read the Built-in Selectors section for more information).

But you can also specify which selector you’re using to do the traversal, and even use your custom defined selectors. This is done using the through keyword:

# Selects the parents of the first basic declaration
from (select first BasicDecl) through parent select *

Attention

There is a special case for Ada, where you can specify follow_generics as a selector name, even though follow_generics is not a selector. This allows traversal of the tree going through instantiated generic trees, but is directly hard-coded into the engine for performance reasons.

# Selects all nodes following generic instantiations
through follow_generics select *

5.2.2. Pattern

pattern value_pattern 'when' expr value_pattern value_pattern '*' upper_id '(' or_pattern ')' '(' pattern_arg ',' ')' upper_id '*' 'null' regex_pattern 'not' value_pattern bool_pattern integer_pattern list_pattern object_pattern id '@' value_pattern '(' or_pattern ')' tuple_pattern

Patterns are by far the most complex part of the query language subset, but at its core, the concept of a pattern is very simple: it is a construction that you will match against a value. LKQL will check that the value matches the pattern, and produce true if it does. In the context of a query, that will add the value to the result of the query.

todo

Patterns are not yet expressions, but they certainly could be and should be, so we’re planning on improving that at a later stage.

5.2.2.1. Node patterns

5.2.2.1.1. Simple Node Patterns

Matching one or many node kinds is the simplest atom for node patterns. It can be either:

  • a node kind name, matching all nodes of this kind

  • an or pattern, matching on multiple node kinds

  • a wildcard pattern, matching on all node kinds

select *                           # Will select every node
select BasicDecl                   # Will select every basic declaration
select (ObjectDecl | BaseTypeDecl) # Will select every object and type declaration

In a more complex form, those can have sub-patterns in an optional part between parentheses, which brings us to the next section.

5.2.2.1.2. Nested Sub Patterns
pattern_arg selector_call pattern_detail_delimiter or_pattern id pattern_detail_delimiter or_pattern fun_call pattern_detail_delimiter or_pattern

Inside the optional parentheses of node patterns, the user can add sub-patterns that will help refine the query. Those patterns can be of three different kinds:

5.2.2.1.3. Selector Predicate

A selector predicate is a sub-pattern that allows you to run a sub-query and to match its results:

select Body(any children: ForLoopStmt)

The quantifier part (any in the previous example) can be either any or all, which will alter how the sub-pattern matches:

  • all will match only if all nodes returned by the selector match the condition

  • any will match as soon as at least one child matches the condition

Any of the built-in selectors can be used, or even custom selectors.

Note

All selectors have three optional parameters that allows controlling the depth of the traversal, depth, max_depth and min_depth. Read Selector Declaration section for more information.

5.2.2.1.4. Field Predicate

A field predicate is a sub-pattern that allows you to match a sub-pattern against a specific field in the parent object. We have already seen such a construct in the introduction, and it’s one of the simplest kind of patterns:

select ObjectDecl(f_default_expr: IntLiteral)
5.2.2.1.5. Property Call Predicate

A property predicate is very similar to a field predicate, except that a property of the node is called, instead of a field accessed. Syntactically, this is denoted by the parentheses after the property name:

select BaseId(p_referenced_decl(): ObjectDecl)

5.2.2.2. Regular Values Patterns

Not only nodes can be matched in LKQL: Any value can be matched via a pattern, including basic and composite data types.

5.2.2.2.1. Integer Pattern
integer_pattern Integer

You can match simple integer values with this pattern:

v is 12
5.2.2.2.2. Bool Pattern
bool_pattern 'true' 'false'

You can match simple boolean values with this pattern:

v is true
5.2.2.2.3. Regex Pattern
regex_pattern String

You can match simple string values with this pattern, but you can also do more complicated matching based on regular expressions:

v is "hello"
v is "hello.*?world"
5.2.2.2.4. Tuple Pattern
tuple_pattern '(' value_pattern ',' ')'

You can match tuple values with this pattern, elements being matched with component patterns:

match i
| (1, 2, 3) => print("un, dos, tres")
| *         => print("un pasito adelante maria")

match i
| (1, a@*, b@*, 4) => { print(a); print(b) }
5.2.2.2.5. List Pattern
list_pattern '[' splat_pattern value_pattern ',' ']'

You can match list values with this pattern, destructuring them and matching their elements against arbitrary value patterns:

match lst
| [1, 2, 3]   => "[1, 2, 3]"
| [1, a@*, 3] => "[1, a@*, 3], with a = " & img(a)

You can use the splat pattern at the end of a list pattern to match remaining elements:

match lst
| [11, 12, ...] => "[11, 12, ...]"
| [1, c@...]    => "[1, c@...] with b = " & img(b) & " & c = " & img(c)
| [...]         => "Any list"
5.2.2.2.6. Object Pattern
object_pattern '{' object_pattern_assoc splat_pattern ',' '}'

You can match object values with this pattern, associating each object key with an arbitrary value pattern:

match obj
| {a: 12}  => "{a: 12}"
| {a: a@*} => "Any object with an a key. Bind the result to a"

You can use the “splat” pattern anywhere in an object pattern to match remaining elements:

match obj
| {a@..., b: "hello"} => "Bind keys that are not b to var a"
| {a@...}             => "Bind all the object to a"

5.2.2.3. Special and Composite Patterns

5.2.2.3.1. Null Pattern

You can match all null nodes with this pattern:

match node
| BasicDecl => "A BasicDecl node"
| null      => "Node is null!"
5.2.2.3.2. Wildcard Pattern

You can match all values with this pattern, it will always return true:

match any_val
| BasicDecl => "A BasicDecl node"
| *         => "Any other value"
5.2.2.3.3. Splat Pattern

This pattern is used inside List Pattern and Object Pattern as a pattern to match all remaining values, collecting them in a collection of the same type as it is used in:

match v
| [1, rem@...]    => "A list with 1 as first element followed by " & img(rem)
| {a: 1, rem@...} => "An object with a=1 and " & img(rem)
5.2.2.3.4. Not Pattern

You can use this pattern to negate another one:

match v
| not BasicDecl => "Everything except a BasicDecl node"
| *             => "A BasicDecl node"
5.2.2.3.5. Or Pattern

You can use this pattern to combine any number of other patterns, and match any value matching one of those:

match v
| (BasicDecl | 1) => "A BasicDecl node or 1"
| *               => "Any other value"

5.2.2.4. Filtered Patterns and Binding Patterns

While you can express a lot of things via the regular pattern syntax mentioned above, sometimes it is necessary to be able to express an arbitrary boolean condition in patterns; this is done via the when clause:

select BasicDecl when bool_condition

However, in order to be able to express conditions on the currently matched objects, or arbitrary objects in the query, naming those objects is necessary. This is done via binding patterns:

select b @ BaseId # Same as "select BaseId", but now every BaseId object
                  # that is matched has a name that can be used in the whole
                  # pattern clause.

# Example usage:
val a = select first BasicDecl
select b @ BaseId when b.p_referenced_decl() == a

5.2.3. Selector Declaration

selector_decl decl_annotation 'selector' id doc_node selector_arm selector_arm '|' pattern '=>' expr

Selectors are a special form of functions that return a LasyList of values. They’re widely used in the query subset of LKQL, allowing the easy expression of traversal blueprints.

For example, by default, a query expression explores the tree via the children built-in selector.

While you can’t add parameters to the definition of a selector, selector calls (a call expression or a selector predicate) can take three optional arguments that allows the control of depth:

  • min_depth allows you to filter nodes for which the traversal depth is lower than a certain value

  • max_depth allows you to filter nodes for which the traversal depth is higher than a certain value

  • depth allows you to only receive nodes that are exactly at the given traversal depth

Here are some examples of calling selectors with those parameters:

# Calling a selectors directly
val c = children(node, depth=3)

# Calling a selector in a nested sub-pattern
select AdaNode(any children(min_depth=3): BasicDecl)

You’ve already seen selectors used in previous sections, and, most of the time, you might not need to define your own, but in case you need to, here is how they work.

5.2.3.1. Defining a Selector

A selector is a recursive function. In the body of the selector, there is a binding from this to the current node. A selector has an implicit top level match expression matching on this.

In the branch of a selector, you can express whatever computation you want for the current node. There is a high-level requirement though, which is that the expression returned by a selector branch must be a RecExpr , which can be created via the call to the rec built-in operation.

The rec built-in operation looks like a function call.

selector_expr 'rec' '(' '*' expr ',' '*' expr ')' 'rec' '(' '*' expr ')'

It takes one or two expressions, which can be prefixed by the splat operator *.

  • The first expression represents what has to be added to the recurse list (either an item, or a list of items, if prefixed by *). The recurse list is the list of items on which the selector will be called next. Items are added at the end of the list

  • The second expression represents what has to be added to the result list (either an item, or a list of items, if prefixed by *). The result list is the list of items that will be yielded, piece-by-piece, to the user.

  • You can pass only one expression, in which case it is used both for the result list and for the recurse list.

Attention

Please note that selector call results are LasyList, thus, their elements are computed on demand (when accessed).

Here is for example how the super_types selector is expressed in LKQL:

selector super_types
| BaseTypeDecl => rec(*this.p_base_types())
| *            => ()

While selectors are in the vast majority of cases used to express tree traversals of graph of nodes, you can use selectors to generate or process more general sequences:

selector infinite_sequence
|" Infinite sequence generator
| nb => rec(
    nb + 1, # Recurse with value nb + 1
    nb # Add nb to the result list
)

fun my_map(lst, fn) =
|" User defined map function. Uses an inner selector to return a lazy
|" iterator result
{
    selector internal
    | idx => rec(
        idx + 1,     # Recurse with value idx + 1
        fn(lst[idx]) # Add the result of calling fn on list[idx] to the result list
    );

    internal(1)
}

val mpd = my_map(infinite_sequence(0), (x) => x * 4)
print(mpd)
print(mpd[51])

Attention

The user interface for selectors is not optimal at the moment, so we might change it again soon.

5.2.3.2. Built-in Selectors

The built-in selectors are:

  • parent: parent nodes

  • children: child nodes

  • prev_siblings: sibling nodes that are before the current node

  • next_siblings: sibling nodes that are after the current node

  • super_types: if the current node is a type, then all its parent types

5.3. Language changes

Under this section, we’ll document language changes chronologically, and categorize them by AdaCore GNATcheck release.

Note

Changes marked as “breaking” indicates that your LKQL code bases need to be migrated when moving to the referred GNATcheck version. The LKQL executable provides a sub-command named refactor to help you doing this (run lkql refactor --help for more information).

5.3.1. 25.0

5.3.1.1. Conditional expression alternatives are now optional

Now you can write a conditional expression without providing any alternative expression. This way, if the condition is evaluated as true, then the consequence expression is evaluated, else the true value is returned. You can use this feature to express logical implication when performing boolean operation, example:

if node.p_has_something() then node.p_check_something_else()

5.3.1.2. Syntax of pattern details (breaking)

Pattern details were specified with the syntax <left_part> is <pattern>, and are now specified with the syntax <left_part>: <pattern>.

5.3.1.3. Syntax of selectors recursion definition (breaking)

The syntax for defining a recursion in selectors has completely changed. The old rec and skip keywords have been replaced by a single rec construct that allows to specify what elements will be recursed upon, and what elements will be yielded by the selector:

selector parent
| AdaNode => rec(*this.parent, this)
#                ^ Add parent to the recurse list
#                ^             ^ Add this to the return list
| *       => ()

Warning

This syntax is more general than the previous one, but is still not optimal, and might change again in a further release. Please take that into account when using selectors in your own code.

More details in the Selector Declaration section.

5.3.1.4. Or patterns syntax (breaking)

Or patterns were defined with the <pattern> or <pattern> syntax, and are now defined with the <pattern> | <pattern> syntax.

5.3.1.5. Binding patterns without value pattern

Patterns binding any value to a name can simply be expressed with a binding name now:

match d
| BasicDecl(p_doc(): doc) => print(doc)

5.3.1.6. More patterns

So far, only node values had corresponding patterns to match them. Now, patterns can be used to match other values:

v is 12
v is true
v is "hello"
v is "hello.*?world"

match i
| (1, 2, 3) => print("un, dos, tres")
| *         => print("un pasito adelante maria")

match i
| (1, a@*, b@*, 4) => { print(a); print(b) }

match lst
| [1, 2, 3]   => "[1, 2, 3]"
| [1, a@*, 3] => "[1, a@*, 3], with a = " & img(a)

match lst
| [11, 12, ...] => "[11, 12, ...]"
| [1, c@...]    => "[1, c@...] with b = " & img(b) & " & c = " & img(c)
| [...]         => "Any list"

match obj
| {a: 12}  => "{a: 12}"
| {a: a@*} => "Any object with an a key. Bind the result to a"

match obj
| {a@..., b: "hello"} => "Bind keys that are not b to var a"
| {a@...}             => "Bind all the object to a"

5.4. LKQL API

5.4.1. Libadalang API

The libadalang API can be called from LKQL and is the basis for most of the GNATcheck rules.

In addition, LKQL comes with a built-in standard library described in Standard library, as well as a LKQL stdlib module described in stdlib’s API doc.

5.4.2. Standard library

5.4.2.1. Builtin functions

unique(indexable)

Given a collection, create a list with all duplicates removed

pattern(regex, case_sensitive)

Given a regex pattern string, create a pattern object

print(to_print, new_line)

Built-in print function. Prints the argument

img(string)

Return a string representation of an object

doc(value)

Given any object, return the documentation associated with it

reduce(iterable, function, init_value)

Given a collection, a reduction function, and an initial value reduce the result

document_builtins()

Return a string in the RsT format containing documentation for all built-ins

base_name(file_name)

Given a string that represents a file name, returns the basename

concat(list)

Given a list, return the result of the concatenation of all its elements

map(iterable, function)

Given a collection, a mapping function

profile(val)

Given any object, if it is a callable, return its profile as text

document_namespace(namespace, name)

Return a string in the RsT format containing documentation for all built-ins

help(value)

Print formatted help for the given object

units()

Return a list of all units

specified_units()

Return a list of units specified by the user

node_checker(root)

Given a root, execute all node checkers while traversing the tree

unit_checker(unit)

Given a unit, apply all the unit checkers on it

5.4.2.2. Builtin methods

5.4.2.2.1. Methods for AnalysisUnit
AnalysisUnit.doc(this)

Given any object, return the documentation associated with it

AnalysisUnit.help(this)

Print formatted help for the given object

AnalysisUnit.img(this)

Return a string representation of an object

AnalysisUnit.name(this)

Return the name for this unit

AnalysisUnit.print(this)

Built-in print function. Prints the argument

AnalysisUnit.root(this)

Return the root for this unit

AnalysisUnit.text(this)

Return the text for this unit

AnalysisUnit.tokens(this)

Return the tokens for this unit

5.4.2.2.2. Methods for Bool
Bool.doc(this)

Given any object, return the documentation associated with it

Bool.help(this)

Print formatted help for the given object

Bool.img(this)

Return a string representation of an object

Bool.print(this)

Built-in print function. Prints the argument

5.4.2.2.3. Methods for Function
Function.doc(this)

Given any object, return the documentation associated with it

Function.help(this)

Print formatted help for the given object

Function.img(this)

Return a string representation of an object

Function.print(this)

Built-in print function. Prints the argument

5.4.2.2.4. Methods for Int
Int.doc(this)

Given any object, return the documentation associated with it

Int.help(this)

Print formatted help for the given object

Int.img(this)

Return a string representation of an object

Int.print(this)

Built-in print function. Prints the argument

5.4.2.2.5. Methods for LazyList
LazyList.doc(this)

Given any object, return the documentation associated with it

LazyList.enumerate(this)

Return the content of the iterable object with each element associated to its index in a tuple: [(<index>, <elem>), …]

LazyList.help(this)

Print formatted help for the given object

LazyList.img(this)

Return a string representation of an object

LazyList.length(this)

Return the length of the iterable

LazyList.print(this)

Built-in print function. Prints the argument

LazyList.reduce(this, function, init_value)

Given a collection, a reduction function, and an initial value reduce the result

LazyList.to_list(this)

Transform into a list

5.4.2.2.6. Methods for List
List.combine(this, right, recursive)

Combine two LKQL values if possible and return the result, recursively if required

List.doc(this)

Given any object, return the documentation associated with it

List.enumerate(this)

Return the content of the iterable object with each element associated to its index in a tuple: [(<index>, <elem>), …]

List.help(this)

Print formatted help for the given object

List.img(this)

Return a string representation of an object

List.length(this)

Return the length of the iterable

List.print(this)

Built-in print function. Prints the argument

List.reduce(this, function, init_value)

Given a collection, a reduction function, and an initial value reduce the result

List.sublist(this, low, high)

Return a sublist of list from low_bound to high_bound

List.to_list(this)

Transform into a list

List.unique(this)

Given a collection, create a list with all duplicates removed

5.4.2.2.7. Methods for MemberReference
MemberReference.doc(this)

Given any object, return the documentation associated with it

MemberReference.help(this)

Print formatted help for the given object

MemberReference.img(this)

Return a string representation of an object

MemberReference.print(this)

Built-in print function. Prints the argument

5.4.2.2.8. Methods for Namespace
Namespace.doc(this)

Given any object, return the documentation associated with it

Namespace.help(this)

Print formatted help for the given object

Namespace.img(this)

Return a string representation of an object

Namespace.print(this)

Built-in print function. Prints the argument

5.4.2.2.9. Methods for Node
Node.children(this)

Return the node’s children

Node.children_count(this)

Return the node’s children count

Node.doc(this)

Given any object, return the documentation associated with it

Node.dump(this)

Dump the node’s content in a structured tree

Node.help(this)

Print formatted help for the given object

Node.image(this)

Return the node’s image

Node.img(this)

Return a string representation of an object

Node.kind(this)

Return the node’s kind

Node.parent(this)

Return the node’s parent

Node.print(this)

Built-in print function. Prints the argument

Node.same_tokens(this, right_node)

Return whether two nodes have the same tokens, ignoring trivias

Node.text(this)

Return the node’s text

Node.tokens(this)

Return the node’s tokens

Node.unit(this)

Return the node’s analysis unit

5.4.2.2.10. Methods for Object
Object.combine(this, right, recursive)

Combine two LKQL values if possible and return the result, recursively if required

Object.doc(this)

Given any object, return the documentation associated with it

Object.help(this)

Print formatted help for the given object

Object.img(this)

Return a string representation of an object

Object.print(this)

Built-in print function. Prints the argument

5.4.2.2.11. Methods for Pattern
Pattern.doc(this)

Given any object, return the documentation associated with it

Pattern.help(this)

Print formatted help for the given object

Pattern.img(this)

Return a string representation of an object

Pattern.print(this)

Built-in print function. Prints the argument

5.4.2.2.12. Methods for PropertyReference
PropertyReference.doc(this)

Given any object, return the documentation associated with it

PropertyReference.help(this)

Print formatted help for the given object

PropertyReference.img(this)

Return a string representation of an object

PropertyReference.print(this)

Built-in print function. Prints the argument

5.4.2.2.13. Methods for RecValue
RecValue.doc(this)

Given any object, return the documentation associated with it

RecValue.help(this)

Print formatted help for the given object

RecValue.img(this)

Return a string representation of an object

RecValue.print(this)

Built-in print function. Prints the argument

5.4.2.2.14. Methods for RewritingContext
RewritingContext.add_first(this, node, new_node)

Insert new_node at the beginning of list_node

RewritingContext.add_last(this, node, new_node)

Insert new_node at the end of list_node

RewritingContext.create_from_template(this, template, grammar_rule, arguments)

Create a new node from the provided template, filling ‘{}’ with provided argument, and parsing the template with the specified grammar rule. Example:

# Create a new BinOp node with OpAdd as operator, representing the addition of the value
# expressed by `my_other_node`, and "42".
ctx.create_from_template(
    "{} + 42",
    "expr_rule",
    [my_other_node]
)
RewritingContext.doc(this)

Given any object, return the documentation associated with it

RewritingContext.help(this)

Print formatted help for the given object

RewritingContext.img(this)

Return a string representation of an object

RewritingContext.insert_after(this, node, new_node)

Insert new_node after node (node’s parent needs to be a list node)

RewritingContext.insert_before(this, node, new_node)

Insert new_node before node (node’s parent needs to be a list node)

RewritingContext.print(this)

Built-in print function. Prints the argument

RewritingContext.remove(this, obj_to_remove)

Delete the given node from its parent (parent needs to be a list node)

RewritingContext.replace(this, old_node, new_node)

Replace old node by the new one

RewritingContext.set_child(this, node, member_ref, new_value)

Set the node child, following the given member reference, to the new value

5.4.2.2.15. Methods for RewritingNode
RewritingNode.clone(this)

Given a rewriting node, clone it and return its copy

RewritingNode.doc(this)

Given any object, return the documentation associated with it

RewritingNode.help(this)

Print formatted help for the given object

RewritingNode.img(this)

Return a string representation of an object

RewritingNode.print(this)

Built-in print function. Prints the argument

5.4.2.2.16. Methods for Selector
Selector.doc(this)

Given any object, return the documentation associated with it

Selector.help(this)

Print formatted help for the given object

Selector.img(this)

Return a string representation of an object

Selector.print(this)

Built-in print function. Prints the argument

5.4.2.2.17. Methods for SelectorList
SelectorList.doc(this)

Given any object, return the documentation associated with it

SelectorList.enumerate(this)

Return the content of the iterable object with each element associated to its index in a tuple: [(<index>, <elem>), …]

SelectorList.help(this)

Print formatted help for the given object

SelectorList.img(this)

Return a string representation of an object

SelectorList.length(this)

Return the length of the iterable

SelectorList.print(this)

Built-in print function. Prints the argument

SelectorList.reduce(this, function, init_value)

Given a collection, a reduction function, and an initial value reduce the result

SelectorList.to_list(this)

Transform into a list

5.4.2.2.18. Methods for Str
Str.base_name(this)

Given a string that represents a file name, returns the basename

Str.combine(this, right, recursive)

Combine two LKQL values if possible and return the result, recursively if required

Str.contains(this, to_find)

Search for to_find in the given string. Return whether a match is found. to_find can be either a pattern or a string

Str.doc(this)

Given any object, return the documentation associated with it

Str.ends_with(this, suffix)

Returns whether string ends with given prefix

Str.find(this, to_find)

Search for to_find in the given string. Return position of the match, or -1 if no match. to_find can be either a pattern or a string

Str.help(this)

Print formatted help for the given object

Str.img(this)

Return a string representation of an object

Str.is_lower_case(this)

Return whether the string is in lowercase

Str.is_mixed_case(this)

Return whether the given string is written in mixed case, that is, with only lower case characters except the first one and every character following an underscore

Str.is_upper_case(this)

Return whether the string is in uppercase

Str.length(this)

Return the string’s length

Str.print(this)

Built-in print function. Prints the argument

Str.split(this, sep)

Given a string, split it on the given separator, and return an iterator on the parts

Str.starts_with(this, prefix)

Returns whether string starts with given prefix

Str.substring(this, start, end)

Given a string and two indices (from and to), return the substring contained between indices from and to (both included)

Str.to_lower_case(this)

Return the string in lowercase

Str.to_upper_case(this)

Return the string in uppercase

5.4.2.2.19. Methods for Token
Token.doc(this)

Given any object, return the documentation associated with it

Token.end_column(this)

Return the end column

Token.end_line(this)

Return the end line

Token.help(this)

Print formatted help for the given object

Token.img(this)

Return a string representation of an object

Token.is_equivalent(this, other)

Return whether two tokens are structurally equivalent

Token.is_trivia(this)

Return whether this token is a trivia

Token.kind(this)

Return the kind for this token

Token.next(this, ignore_trivia)

Return the next token

Token.previous(this, exclude_trivia)

Return the previous token

Token.print(this)

Built-in print function. Prints the argument

Token.start_column(this)

Return the start column

Token.start_line(this)

Return the start line

Token.text(this)

Return the text for this token

Token.unit(this)

Return the unit for this token

5.4.2.2.20. Methods for Tuple
Tuple.doc(this)

Given any object, return the documentation associated with it

Tuple.help(this)

Print formatted help for the given object

Tuple.img(this)

Return a string representation of an object

Tuple.print(this)

Built-in print function. Prints the argument

5.4.2.2.21. Methods for Unit
Unit.doc(this)

Given any object, return the documentation associated with it

Unit.help(this)

Print formatted help for the given object

Unit.img(this)

Return a string representation of an object

Unit.print(this)

Built-in print function. Prints the argument

5.4.3. stdlib’s API doc

5.4.3.1. Functions

all(iterable)

Return whether all elements in the given iterable are truthy

any(iterable)

Return whether at least one element in the given iterable is truthy

closest_enclosing_generic(n)

If n is part of a generic package or subprogram, whether it is instantiated or not, then return it.

default_bit_order()

Return the value of System.Default_Bit_Order if any with System clause is found, null otherwise.

depends_on_mutable_discriminant(component_decl)

Given a ComponentDecl, return whether it depends on a mutable discriminant value coming from its parent record declaration. The component depends on a discriminant if it uses it in its subtype constraint or if it is a variant.

enclosing_block(n)

Return the first DeclBlock enclosing n if any, null otherwise.

enclosing_body(n)

Return the first BodyNode enclosing n if any, null otherwise

enclosing_package(n)

Return the first BasePackageDecl or PackageBody enclosing n if any, null otherwise

find_comment(token, name)

Return true if a comment token immediately following the previous “begin” keyword is found and contains only the provided name.

first_non_blank(s, ind=1)

Return the index of the first non blank character of s, starting at ind

full_root_type(t)

Return the full view of the root type of t, traversing subtypes, derivations and privacy.

get_parameter(params, actual)

Given a List[ParamActual], return the parameter corresponding to actual, null if actual is not found.

get_subp_body(node)

Return the SubpBody, TaskBody or ExprFunction corresponding to node, if any, null otherwise.

has_interfaces(n)

Return true if n is an interface or implements some interfaces

has_local_scope(n)

Return true if n is enclosed in a local scope

has_non_default_sso(decl)

Return true if decl has a Scalar_Storage_Order aspect whose value cannot be determined to be equal to System.Default_Storage_Order.

in_generic_instance(n)

Return true if n is part of a generic instantiation.

in_generic_template(n)

Return true if n is declared as part of a generic template (spec or body). Return false otherwise, including inside a generic instantiation.

is_assert_aspect(s)

Return true if the string s is the name of an assert aspect

is_assert_pragma(s)

Return true if the string s is the name of an assert pragma

is_by_copy(param)

Return true if param (a ParamActual) has a non aliased by-copy type

is_classwide_type(t)

Return true if t is a classwide TypeDecl.

is_composite_type(decl)

Given a BaseTypeDecl, returns whether the declared type is a composite Ada type (record, array, task or protected).

is_constant_object(node)

Return true is node represents a constant object, false otherwise

is_constructor(spec)

Return true if spec is a subprogram spec of a constructor, that is, has a controlling result and no controlling parameter.

is_controlling_param_type(t, spec)

Return true if t is a TypeExpr corresponding to a controlling parameter of the subprogram spec spec.

is_in_library_unit_body(o)

Return true if o is located in a library unit body

is_in_package_scope(o)

Return true if o is immediately in the scope of a package spec, body or generic package.

is_limited_type(type)

Return true if type is a limited type

is_local_object(o)

Return true if o represents a local ObjectDecl or ParamSpec

is_negated_op(node)

Return whether node is a “not” unary operation, returning a standard boolean, and having as operand a predefined RelationOp or UnOp with OpNeq as operator.

is_predefined_op(op, follow_renamings=false)

Return true if op is a predefined operator; op can be an Op or a CallExpr.

is_predefined_type(n)

Return true if n is the name of a type declared in a predefined package spec.

is_program_unit(n)

Return true if n is a program unit spec, body or stub

is_standard_boolean(n)

Return true if the root type of n is Standard.Boolean.

is_standard_false(node)

Get whether the given node is a Name representing the standard False value.

is_standard_numeric(n)

Return true if n is the name of a numeric type or subtype in Standard

is_standard_true(node)

Get whether the given node is a Name representing the standard True literal.

is_tasking_construct(node)

Returns whether the given node is a construct related to Ada tasking, in other words: All constructs described in the section 9 of Ada RM.

is_unchecked_conversion(node)

Return true if node represents an instantiation of the Ada.Unchecked_Conversion subprogram

is_unchecked_deallocation(node)

Return true if node represents an instantiation of the Ada.Unchecked_Deallocation subprogram

list_of_units()

Return a (cached) list of all known units

max(x, y)

Return the max value between x and y

negate_op(node)

Assumes that node is either a RelationOp or UnOp with the OpNot as operator. Returns the negated form of the operation as a rewriting node. Examples: negate_op("A = B") -> "A /= B" negate_op("A > B") -> "A <= B" negate_op("not A") -> "A"

next_non_blank_token_line(token)

Return the start line of the next non blank token, or the next line for a comment, or 0 if none.

number_of_values(type)

Return the number of values covered by a given BaseTypeDecl, -1 if this value cannot be determined.

param_pos(n, pos=0)

Return the position of node n in its current list of siblings

previous_non_blank_token_line(token)

Return the end line of the previous non blank token, or the previous line for a comment, or 0 if none.

propagate_exceptions(body)

Return true if the given body may propagate an exception, namely if: - it has no exception handler with a when others choice; - or it has an exception handler containing a raise statement, or a call to Ada.Exception.Raise_Exception or Ada.Exception.Reraise_Occurrence.

range_values(left, right)

Return the number of values covered between left and right expressions, -1 if it cannot be determined.

sloc_image(node)

Return a string with basename:line corresponding to node’s sloc

strip_conversions(node)

Strip ParenExpr, QualExpr and type conversions

ultimate_alias(name, all_nodes=true, strip_component=false)

Return the ultimately designated ObjectDecl, going through renamings This will not go through generic instantiations. If all_nodes is true, consider all kinds of nodes, otherwise consider only BaseId and DottedName. If strip_component is true, go to the prefix when encountering a component, otherwise stop at the ComponentDecl.

ultimate_designated_generic_subp(subp_inst)

Given a node representing an instantiation of a generic subprogram, return that non-instantiated subprogram after resolving all renamings.

ultimate_exception_alias(name)

Return the ultimately designated ExceptionDecl, going through renamings

ultimate_generic_alias(name)

Return the ultimately designated GenericDecl, going through renamings

ultimate_prefix(n)

Return n.f_prefix as long as n is a DottedName and designates a ComponentDecl, n otherwise.

ultimate_subprogram_alias(name)

Return the ultimately designated BasicSubpDecl, going through renamings

within_assert(node)

Return true if node is part of an assertion-related pragma or aspect.

5.4.3.2. Selectors

children_no_nested()

Return all children nodes starting from a base subprogram body, but not entering in nested bodies.

complete_super_types()

Yields the chain of super types of the given type in their most complete view. Hence, for a type T which public view derives from a type A but private view derives from a type B (which itself derives from A), invoking this selector on the public view of T will yield B and then A.

component_types()

Return all the BaseTypeDecl corresponding to all fields of a given type, including their full views, base types and subtypes.

full_parent_types()

Return all base (sub)types full views

parent_decl_chain()

Return all parent basic decl nodes starting from a given node, using semantic parent. When on a subprogram or package body, go to the declaration This allows us to, if in a generic template, always find back the generic formal.

semantic_parent()

Return all semantic parent nodes starting from a given node.

super_types()

Yields the chain of super types of the given type, as viewed from that type. Hence, for a type T which public view derives from a type A but private view derives from a type B (which itself derives from A), invoking this selector on the public view of T will yield A.