Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

grammar for prolog

202 views
Skip to first unread message

Henk Schouten

unread,
Oct 3, 1989, 6:36:10 AM10/3/89
to

Hello netlanders,

I am looking for a description of the grammar of the Prolog language to be
used in building a syntax checker with Lex/Yacc. Since building the syntax
checker is a learning project for students any pointers to existing syntax
checkers for Prolog won't help.

+-----------------------------------------------------------------------------+
| Henk Schouten Software Expertise Center |
| Haagse Hogeschool - Intersector Informatica |
| Louis Couperusplein 1-19 |
| henks@hhinsi@hp4nl 2419 AP Den Haag - The Netherlands |
| henks@nikhef@hp4nl tel: (31) 70 618419 fax: (31) 70 618599 |
+-----------------------------------------------------------------------------+

Richard O'Keefe

unread,
Oct 4, 1989, 4:04:25 AM10/4/89
to
In article <5...@nikhefk.UUCP>, he...@nikhefk.UUCP (Henk Schouten) writes:
> I am looking for a description of the grammar of the Prolog language to be
> used in building a syntax checker with Lex/Yacc. Since building the syntax
> checker is a learning project for students any pointers to existing syntax
> checkers for Prolog won't help.

(A) There is a public-domain tokeniser for Prolog and a public-domain
parser for Prolog. I wrote the tokeniser and adapted the parser,
and posted both to the net in '84. Both are Prolog source code.
I know you say "any pointers to existing .. won't help", but the
tokeniser and parser are about as concise a specification of Prolog
syntax as you will get.

(B) However, Prolog is an extensible language. The lexical structure
is not extensible, so you could use Lex. I have a table-driven
tokeniser in C (I've been using it in an editor for years, and it
was donated to Stony Brook Prolog), so I know you can do that part
statically as Lex requires. The extension mechanism of Prolog is
that you can declare new operators, which can be prefix, infix,
postfix, or any mix of them. For example, after doing
:- op(100, fx, a).
the expression "a X" is legal, "a a X" is illegal, "a(X)" and "a = X"
are legal and would have been without the declaration.
Had the declaration been
:- op(800, fy, a).
the expression "a a X" would have been legal and "a = X" illegal.
After the declarations
:- op(100, fx, a), op(100, xf, a), op(100, xfx, a)
the expressions "a X", "X a", and "X a X" are all legal.
It is easy to find small sets of operator declarations which make
Prolog not LR(k) for any fixed k, still less LR(1).

Some extensible languages (such as Algol 68) can be hacked by having
a fixed set of operator meta-tokens, PREFIX_1, ... INFIX_9 and the
like, and having the tokeniser return those. However, Prolog has
1200 precedence levels, so that would be rather a strain for Yacc.

(C) The BSI/ISO committees have produced several different grammars for
Prolog. I believe the current version to be the one in a document
ISO/IEC JTC1 SC22 WG17 N40, dated July 1989. This one is pretty
straightforward. (Unlike the version which I criticsed so strongly
in this newsgroup, the current version makes no attempt to describe
the syntax of Prolog code. It is frankly a syntax for TERMS, and as
such nearly all of my objections no longer apply.) This document
should be available from NPL.

(D) Prolog is much more like Lisp than it is like Pascal. It is
possible to define a (non-LR(1)) grammar for Prolog *data*, but
every Prolog procedure is made of Prolog data, and "telling the
birds from the flowers" is not always possible. Consider the fact
that many Prolog systems have a macro-expansion predicate called
term_expansion/2 which users can define at run-time. For example,
after defining

:- op(10, fx, a).
:- op(10, fx, an).

term_expansion(X is a Y, Fact) :- Fact =.. [Y,X].
term_expansion(X is an Y, Fact) :- Fact =.. [Y,X].

the clauses

clyde is an elephant.
lr(1) is a restriction.

behave to a Prolog system exactly as if they had been written

elephant(clyde).
restriction(lr(1)).

For semantic analysis, it is the term which results from such
user-defined macro-processing (this includes grammar rule expansion)
that matters. There can be no difference in meaning between

X is (Y+1)/2

and

is(X, /(+(Y,1),2))

because they are the SAME term, even though there is a syntactic
difference.

There are Prolog systems which do not offer term_expansion/2, and they
can be very useful if they are otherwise excellent, but it is a
definite restriction to leave this facility out.

(E) The bottom line is that Yacc is not able to handle the full syntax
of Prolog. You would have to restrict it by leaving out user-defined
operators and user-defined macro-processing. The result would still
be a useful language. But it would not be a very interesting one to
use as a class project, because there is very little that a syntactic
analysis can reject. Consider:

p :- 2.

does not make sense as a Prolog rule, because 2 is not something that
can be called. (Although some Prolog systems use precisely this
syntax to tie basic operations to special instructions.) However,

q :- nonvar(( p :- 2 )).

is perfectly sensible. The Prolog parser in my editor is, excluding
the tokeniser, about 200 lines of C. About a third of that is
disambiguating operators. That really doesn't sound as though it
would make an interesting Yacc grammar.

Helge Oldach

unread,
Oct 9, 1989, 2:50:03 PM10/9/89
to
In article <22...@munnari.oz.au>, o...@cs.mu.oz.au (Richard O'Keefe) writes:
> In article <5...@nikhefk.UUCP>, he...@nikhefk.UUCP (Henk Schouten) writes:
> > I am looking for a description of the grammar of the Prolog language to be
> > used in building a syntax checker with Lex/Yacc.
> [...]

> (E) The bottom line is that Yacc is not able to handle the full syntax
> of Prolog. You would have to restrict it by leaving out user-defined
> operators and user-defined macro-processing. The result would still
> be a useful language. But it would not be a very interesting one to
> use as a class project, because there is very little that a syntactic
> analysis can reject.

I agree. My solution (some years ago) was to write an operator precedence
parser for Prolog. The syntax is very straightforward: you just have
operands, operators and brackets. And (this was my main motivation):
there was no harm implementing extensible sets of operators.

> The Prolog parser in my editor is, excluding
> the tokeniser, about 200 lines of C. About a third of that is
> disambiguating operators. That really doesn't sound as though it
> would make an interesting Yacc grammar.

I agree, again. My parser was (I hope, it still *is* :-)) very small, too.

rockbr...@gmail.com

unread,
Aug 24, 2016, 6:33:02 PM8/24/16
to
The beauty of USENET is that the passage of time has no meaning; perfectly suiting us vampires and immortals for whom 1989 is just a short while ago...

Bear in mind, I've recently (re)implemented AUTOMATH and am rapidly migrating it to a new and higher form -- with the intent on subsuming everything out there -- and as a first step I'm going to be putting a Prolog operator syntax on it like that described below. Releases of snapshots of my copy AUTOMATH are available by e-mail.

On Tuesday, October 3, 1989 at 5:36:10 AM UTC-5, Henk Schouten wrote:
> Hello netlanders,
> I am looking for a description of the grammar of the Prolog language to be
> used in building a syntax checker with Lex/Yacc. Since building the syntax
> checker is a learning project for students any pointers to existing syntax
> checkers for Prolog won't help.

This is an old file I have; it may be partly based on a redaction of the (mostly defunct) ISO standard or some books on Prolog; I don't remember.

The fundamental syntactic construct in Prolog is the term. At the topmost level, itself, the terms are interpreted as sentences in the manner described below. There is a limited ability to define or redefine the syntax of terms, these facilities, therefore, are also available for defining the syntax of sentences.

Each term comprises a sequence of tokens; each token, in turn, being treated as a single symbol that is spelled out in 1, 2 or more characters. The tokens include those for variables, constants, functors as well as brackets and punctuation. The token composition of a term is described in further detail below. The spellings of the tokens are also described in further detail below.

When a sequence of tokens is read in, it must be terminated by the full-stop token. Wherever the concatenation of two or more tokens would produce the spelling of another token, the tokens need to be separated by a layout-text token in order to prevent the misreading. The layout-text tokens may be arbitrarily interspersed in a program and serve no other function than to separate other tokens.

For what follows A* denotes 0, 1, 2 or more or A; [A] denotes 0 or 1 of A; "..." denotes literals

All the phrase types S = sentences; H = grammar rule head; B = grammar rule body are specializations of the syntax T for terms and are separated out only for convenience. The top-level phrase type -- and only real phrase type in the Prolog syntax is just T itself. The reason for mentioning this is that T is indexed by precedence levels and all the unary prefix, unary postfix and binary infix operators have precedence levels -- including those that appear in the syntax for S, H and B. So I don't list explicit precedence levels for these three categories. A parser need only parse the syntax for T and pass the refined interpretations of terms within the categories S, H and B downstream for the semantic analyzer to handle.

Sentences
S -> a ":" S Sentence labeled by module name
S -> L A sentence in list form
S -> H [":-" B] Clause
If :- B is absent,
H must not be otherwise interpretable as a sentence)
S -> ":-" B Command
S -> "?-" B Query
S -> H "->" B Grammar rule

H -> a ":" H Module label
H -> T Goal; T may not be an X
or have any of , ; : \+ -> as its main operator.

B -> a ":" B Module label
B -> B "->" B ";" B Conditional
B -> B "->" B Elseless conditional
B -> "\+" B
B -> B ";" B Disjunction
B -> B "," B Sequencing
B -> T Goal; T may not be an X
or have any of , ; : \+ -> as its main operator.

In a grammar rule, instances of H or B of the forms L or S are interpreted respectively as a list of terminals or as a literal terminal; instances of B of the forms { B } or ! are interpreted as conditions; instances of H or B of the forms T are interpreted as non-terminals. In H or B, instances of T may not have the form of a variable X, or contain any of the operators , ; \+ -> as their main operator.

Terms
As mentioned previously, when a sequence of tokens comprising a term is read in, it must end in a full-stop. The syntax is: T(1200) full-stop. There are a set of precedence levels, ranging from 0 to 1200, for terms. This facility is provided to allow certain operators and punctuation to bind more tightly than others, and it is available to enable one to partially define or redefine the syntax of terms.

T -> T(1200);
T(n+1) -> T(n) for all integer n in the half-open interval [0,1200).

T(n) -> fx(n) T(n-1) except for number.
T(n) -> fy(n) T(n)
T(n) -> T(n-1) xfx(n) T(n-1)
T(n) -> T(n-1) xfy(n) T(n)
T(n) -> T(n) yfx(n) T(n-1)
T(n) -> T(n-1) xf(n)
T(n) -> T(n) yf(n)

T(1000) -> T(999) "," T(1000) The comma operator is xfy(1000).
T(0) -> a ["(" T(999) ("," T(999))* ")"] Function or constant.
T(0) -> "(" T(1200) ")'
T(0) -> "{" T(1200) "}"
T(0) -> L Lists
T(0) -> S Strings
T(0) -> N Numeric Constants
T(0) -> X Variables

L -> "[" [T(999) ("," T(999))* ["|" T(999)]] "]"
(The Prolog syntax apparently doesn’t allow two or more T(999)
to precede the separator "|".)

N -> ["+"|"-"] Numeral
N -> ("+"|"-") ("inf" | "nan")

All the tokens fx(n), fy(n), xfx(n), xfy(n), yfx(n), xf(n), yf(n) are instances of the atom, a, which have been specially declared as the respective operators of the respective precedences and associativities. The operators of the respective forms ?f, ?f? and f? are prefix, infix and postfix. Those of the forms yf* are left-associative and those of the form *fy are right-associative.

The comma operator "," is fixed in the syntax above as of type xfy(1000). A term T(1000) of the form A,B is interpreted in the standard syntax as ‘,’(A,B); while the terms T(0) of the form {A} and (A) are interpreted, respectively, as ‘{}’(A) and A. All the other prefix, infix and postfix operators can be written in ordinary function syntax like this by quoting them.

In order to disambiguate between an operator followed by a parenthesis versus a function-call, a requirement is imposed that "(" must immediately follow the a of the function in a function call, and "(" must be separated from fx(n) or fy(n) in an operator application.

For those of you C/C++ programmers who prefer to space out function brackets -- contravening centuries of mathematical tradition by the way -- PPHHHHTHHHHT!!

Also, in case of ambiguity, the interpretation of an instance of an atom a as a prefix operator, fx(n) or fy(n), wherever possible, wins out; and the interpretation of an instance of xf(n) or yf(n) as xfx(n), xfy(n) or yfx(n), wherever possible, wins out.

Tokens
The following is what a lexer will see, process and pass on down to the parser. I won't get into internationalization details on the character sets.

As above, I quote literals -- here literal characters. The quote itself " is quoted as "\"", like in C; while \ is quoted as "\\". The newline is quoted as "\n", the tab as "\t" and space as " ".

The roster of character categories and their minimal membership are:

White "\t", "\n", " "
Lower "a", "b", "c", "d", "e", "f", "g", "h", "i",
"j", "k". "l", "m", "n", "o", "p", "q", "r",
"s", "t", "u", "v", "w", "x", "y", "z"
Upper "A", "B", "C", "D", "E", "F", "G", "H", "I",
"J", "K". "L", "M", "N", "O", "P", "Q", "R",
"S", "T", "U", "V", "W", "X", "Y", "Z"
Digit "0", "1", "2", "3", "4",
"5", "6", "7", "8", "9"
Symbol "+", "-", "*", "/", "\\", "^", "`", "~", "."
"<", ">", "=", ";", "?", "@", "#", "$", "&"
Solo "!", ";"
Punctuation "%", "(", ")", ",", "|",
"[", "]", "{", "}"
Quote "\"", "'"
Underline "_"

The top-level of the lexer is Token* -- a stream or 0, 1, 2 or more tokens; with the following lexical syntax.

Token -> a
Token -> Numeral
Token -> X
Token -> S
Token -> Punctuation
Token -> Layout+
Token -> Done

a -> "'" C* "'"
a -> Lower (Upper | Lower | Digit | Underline)*
a -> Symbol+
a -> Solo
a -> "[" Layout* "]"
a -> "{" Layout* "}"

Neither the full-stop nor any symbol sequence starting in "/*" counts as an a.

Numeral -> Digit+
Numeral -> Digit+ "'" (Upper | Lower | Digit)*
Numeral -> "0" "'" C
Numeral -> Digit+ "." Digit+ [["e"|"E"] ["+"|"-"] Digit+]

Prolog, similar to languages like BC, allows a wide range of radices. That's what the apostrophe "'" is for. In the base-radix notation R'N, the digits comprising N must be of value no larger than R, with a,b,… and A,B,… both being treated as being of values 10,11,…. The base R must in the range [2,36]. Note that –3 is identified as a numeral, whereas –(3) is an application of the operator – to the numeral 3.

X -> ("_" | Upper) (Upper | Lower | Digit | Underline)*
S -> "\"" C* "\""

C -> any Char, other than "\\"
C -> "\\" Esc

In the atom a, a quoted "'" must be duplicated. In a string S, "\"" must be duplicated.

Layout -> White
Layout -> "/*" Char* "*/"
Layout -> "%" Char* "\n"

The character sequences in the "/*" and "%" comments may not contain the respective ending sequences "*/" or "\n" within them; they may only be used to close the respective comments -- i.e. no nesting of any comments are permitted within comments of the same type.

Done -> "."

A full stop must be separated from subsequent tokens by LayoutItems.

Char -> Any character, including White, Lower, Upper, Digit, Underline, Symbol, Solo, Punctuation and Quote.

Esc -> "a"|"b"|"t"|"n"|"v"|"f"|"r"|"e"|"d"
Esc -> "x" (Upper | Lower | Digit) (Upper | Lower | Digit)
Esc -> Digit [Digit] [Digit]
Esc -> "^" ("?" | Upper | Lower)
Esc -> "c" White*
Esc -> White
Esc -> Char

The single-character escapes are, respectively, the alarm, backspace, horizontal tab, newline, vertical tab, form feed, carriage return, escape and delete. The escapes starting in x are hexadecimal escapes; with the following characters ranging from 0-9, A-F and a-f. The escapes starting in a digit are octal escapes, and the digits must all be in the range 0-7. The escapes starting in ^ are control-sequences, with ^? standing for delete (127) and the corresponding codes for the other controls being taken as the code of the character following the ^, modulo 32. Escape sequences involving layout are ignored (and that starting in c is taken with the longest layout sequence that occurs following it), and the escape sequence of any other character is taken to stand for the character, itself.

Older implementations of Prolog do not share this lexical syntax for Esc and I do not believe the lexical syntax for character escape is mandatory.

j4n bur53

unread,
Aug 25, 2016, 6:08:35 AM8/25/16
to
rockbr...@gmail.com schrieb:
> Bear in mind, I've recently (re)implemented AUTOMATH and am
> rapidly migrating it to a new and higher form -- with the
> intent on subsuming everything out there -- and as a
> first step I'm going to be putting a Prolog operator
> syntax on it like that described below. Releases of
> snapshots of my copy AUTOMATH are available by e-mail.

For theorem proving I would suggest that your syntax
can swallow unicode. So that you can directly enter
symbols such as

:- op(900, fy, ∀).
:- op(900, fy, ∃).
:- op(700, xfx, ∈).

Otherwise it doesn't make sense to reinvent variations
of Prolog syntax. Prolog syntax is already defined
in the ISO core standard.

It doesn't make sense for example to drop something
from the^syntax, replace it by something else. It only
makes sense to define extensions.

So what is wrong in your syntax compared to ISO:

T(0) -> a ["(" T(999) ("," T(999))* ")"] Function or constant.
Corr.: Its not exactly your a here, if token is DIRECTLY
followed by "(" it can be much more:

Welcome to SWI-Prolog (Multi-threaded, 64 bits, Version 7.3.25)
Copyright (c) 1990-2016 University of Amsterdam, VU Amsterdam

?- X = ;(a,b).
X = (a;b).

?- X = ,(a,b).
ERROR: Syntax error: Operator expected
ERROR: X =
ERROR: ** here **
ERROR: ,(a,b) .

Lets call this thing a1.

T(n) -> T(n-1) xfx(n) T(n-1) Etc..
Corr.: Well, well, you need also to define what syntax
xfx, etc.. has. Unfortunately its not the full a1,
some atoms can be used as functors but not as operators.

Welcome to SWI-Prolog (Multi-threaded, 64 bits, Version 7.3.25)
Copyright (c) 1990-2016 University of Amsterdam, VU Amsterdam

?- X = (a ; b).
X = (a;b).

?- X = (a , b).
X = (a, b).

Lets call this thing a2.

N -> ("+"|"-") ("inf" | "nan")
Corr.: Could be an extension, but why?
(ISO evaluator doesn't support inf and nan)

Symbol "+", "-", "*", "/", "\\", "^", "`", "~", "."
"<", ">", "=", ";", "?", "@", "#", "$", "&"
Corr.: Symbol "+", "-", "*", "/", "\\", "^", "~", "."
"<", ">", "=", "?", "@", "#", "$", "&"

Punctuation "%", "(", ")", ",", "|",
"[", "]", "{", "}"
Corr: Punctuation "(", ")", ",", "|",
"[", "]", "{", "}"

S -> "\"" C* "\""
Corr. S -> "\"" C* "\"" | "`" C* "`"

Esc -> "x" (Upper | Lower | Digit) (Upper | Lower | Digit)
Corr.: Esc -> "x" HexDigit { HexDigit } "\\"

Esc -> Digit [Digit] [Digit]
Corr.: Esc -> Digit { Digit } "\\"

Esc -> "^" ("?" | Upper | Lower)
Corr.: Could be an extension, but why?
(ISO redundant to existing escapes)

Esc -> "c" White*
Corr.: Could be an extension, but why?
(ISO redundant to existing escapes)

Esc -> Char
Corr.: Could be an extension, but why?
(ISO has more safety in not allowing this)

Bye

rupert...@googlemail.com

unread,
Aug 25, 2016, 11:44:56 AM8/25/16
to
On Wednesday, August 24, 2016 at 11:33:02 PM UTC+1, rockbr...@gmail.com wrote:
> Terms
> As mentioned previously, when a sequence of tokens comprising a term is read in, it must end in a full-stop. The syntax is: T(1200) full-stop. There are a set of precedence levels, ranging from 0 to 1200, for terms. This facility is provided to allow certain operators and punctuation to bind more tightly than others, and it is available to enable one to partially define or redefine the syntax of terms.
>
> T -> T(1200);
> T(n+1) -> T(n) for all integer n in the half-open interval [0,1200).
>
> T(n) -> fx(n) T(n-1) except for number.
> T(n) -> fy(n) T(n)
> T(n) -> T(n-1) xfx(n) T(n-1)
> T(n) -> T(n-1) xfy(n) T(n)
> T(n) -> T(n) yfx(n) T(n-1)
> T(n) -> T(n-1) xf(n)
> T(n) -> T(n) yf(n)

Does this work?

Here is what I came up with to handle dynamic operators in Prolog:

https://github.com/rupertlssmith/lojix/blob/master/lojix/logic/src/main/com/thesett/aima/logic/fol/isoprologparser/DynamicOperatorParser.java

Ulrich Neumerkel

unread,
Aug 25, 2016, 9:20:30 PM8/25/16
to
j4n bur53 <janb...@fastmail.fm> writes:
>rockbr...@gmail.com schrieb:
>> Bear in mind, I've recently (re)implemented AUTOMATH and am
>> rapidly migrating it to a new and higher form -- with the
> > intent on subsuming everything out there -- and as a
> > first step I'm going to be putting a Prolog operator
> > syntax on it like that described below. Releases of
> > snapshots of my copy AUTOMATH are available by e-mail.
>
...
>Otherwise it doesn't make sense to reinvent variations
>of Prolog syntax. Prolog syntax is already defined
>in the ISO core standard.

Indeed, the syntax contains many archaic constructs like
the \^ escape sequences. Many current systems simply
reject those. And those that don't expose three
behaviours that are all incompatible to each other.
See the following case:

http://www.complang.tuwien.ac.at/ulrich/iso-prolog/conformity_assessment#284

j4n bur53

unread,
Sep 24, 2016, 11:35:28 AM9/24/16
to
Hi Ulrich,

LPA Prolog has also tons of special syntax:

'~I' represents ctrl-I.

See here:
http://www.lpa.co.uk/dow_doc.htm
Try WIN_PRG.PDF

Ulrich Neumerkel schrieb:

j4n bur53

unread,
Sep 24, 2016, 11:36:41 AM9/24/16
to
And also:

The tilde character can also be followed by a hexadecimal integer within
brackets representing the character code of a character. This can be
useful for inserting characters with a character code greater than 7Fh
(127).

j4n bur53 schrieb:

kint...@gmail.com

unread,
Oct 4, 2016, 1:27:15 AM10/4/16
to
> I am looking for a description of the grammar of the Prolog language to be
> used in building a syntax checker with Lex/Yacc. Since building the syntax
> checker is a learning project for students any pointers to existing syntax
> checkers for Prolog won't help.

the yap user manual documentation has excellent descriptions of the syntax .
it should be all you need .

~~~ kintalken

j4n bur53

unread,
Oct 20, 2016, 8:26:53 AM10/20/16
to
<experimental>

Here is a little Unicode challenge (Arabic Numerals):

Preview of upcoming Release 1.1.7 Jekejeke Prolog:

/* Numeral 4 and 6 in Arabic */
?- char_code('٤', X).
X = 1636
?- char_code('٦', X).
X = 1638

/* Numeral classification */
?- use_module(library(misc/text)).
% 1 consults and 0 unloads in 21 ms.
Yes
?- char_type('٤', X).
X = digit
?- char_type('٦', X).

/* Decimal numbers */
?- X = ٤٦.
X = 46

/* Hex numbers and escapes */
?- X = 0x٤٦.
X = 70
?- X = '\x٤٦\'.
X = 'F'

/* Octal numbers and escapes */
?- X = 0o٤٦.
X = 38
?- X = '\٤٦\'.
X = &

Current version 7.3.28 of SWI-Prolog:

/* Numeral classification */
?- char_type('٤', X).
X = alnum ;
X = csym ;
X = prolog_identifier_continue ;
X = digit ;
X = graph ;
X = to_lower('٤') ;
X = to_upper('٤') ;
false.

/* Decimal numbers */
?- X = ٤٦.
ERROR: Syntax error: Operator expected
ERROR: X =
ERROR: ** here **
ERROR: ٤٦ .

/* Hex numbers */
?- X = 0x٤٦.
ERROR: Syntax error: Illegal number
ERROR: X =
ERROR: ** here **
ERROR: 0x٤٦ .

/* Octal numbers */
?- X = 0o٤٦.
ERROR: Syntax error: Illegal number
ERROR: X =
ERROR: ** here **
ERROR: 0o٤٦ .

Bye

P.S.: New scanner token is going to be open source:
https://github.com/jburse/jekejeke-devel/tree/master/utils/headless/matula/util/regex

Still some issues with some of Ulrich Neumerkels test cases,
since I was temporarily lowering the look ahead, so floats
don't work exactly in release 1.1.7 as they worked in release
1.1.6, might be fixed in release 1.1.8.

</experimental>

Ulrich Neumerkel schrieb:
0 new messages