Code Monkey home page Code Monkey logo

trivia's Introduction

https://travis-ci.org/guicho271828/trivia.svg?branch=master

  • news! new pattern: lambda-list pattern. Contributed by akssri
  • news! new pattern: number-related patterns, e.g. >, <, =, <= …
  • news! Inline pattern implemented ! : @, @@ …
  • news!(04/02/2016) Support for fare-quasiquote is now available. See test/quasiquote for the usage
  • news!(04/22/2016) Added metabang-bind like macros if-match, when-match, unless-match, let-match, let*-match, let-match1
  • news!(05/21/2016) Added support for minor implementations: CMU, ECL, CLISP, ABCL.
  • news!(05/22/2016) Implemented ARRAY, SIMPLE-ARRAY, ARRAY-ROW-MAJOR, ARRAY-ROW-MAJOR* patterns! Multi-dimentional arrays are now more handy!
  • news!(07/21/2016) Added READ, LAST, SPLIT, SPLIT* patterns! Parsing the string is more conveninent.
  • news!(01/21/2017) Added DYNAMIC pattern! Careful use of this pattern can impact the performance sensitive code.
  • news!(04/08/2017) Added a new contrib package TRIVIA.CFFI which provides -> pattern ! Offers convenient access to foreign objects.
  • news!(05/26/2018) Added property!, which only matches when the key is present in a plist.
  • news!(09/06/2018) SPLIT symbol was exported from the trivia.ppcre package.
  • news!(02/19/2019) Added MEMBER pattern. When the argument is a constant, it also adds type declaration.
  • news!(04/24/2019) Improved the compilation of GUARD pattern. It no longer uses the internal hackery.
  • news!(04/24/2019) Balland2006 optimizer is now the default optimizer for the pattern compiler!
  • news!(04/28/2019) Added a progv pattern, which can dynamically alter the dynamic variable the value will be bound to.
  • news!(05/08/2019) Now the optimizer can be specified in the lexical environment via (declare (trivia:optimizer <name>)) (e.g. (declare (trivia:optimizer :trivial))). Implemented through cltl2 API.
  • news!(10/11/2019) The OR1 consistency checking algorithm in Level 1 no longer takes the exponential runtime. Compilation of type-r library is now 10x faster! (patch from @pfdietz)
  • news!(01/01/2021) Added HASH-TABLE-ENTRY, HASH-TABLE-ENTRIES patterns, and corresponding ! suffixed patterns for matching only if key is present in hash table.
  • news!(05/30/2021 Added support for FSet. See tests for how-to.

Trivia : Trivial Pattern Matching Compiler

Trivia is a pattern matching compiler that is compatible with Optima. It shares the same testing code with Optima and acts as a drop-in replacement for 99% usage. For the basic usage, consult our wiki. Known differences between Optima and Trivia, which are bug, are described here (7/31/2016)

(defpackage :playwithit
  (:use :cl 
-       :optima))
+       :trivia))
(in-package :playwithit)

(match '(something #(0 1 2))
  ((list a (vector 0 _ b))
   (values a b)))
;; --> SOMETHING, 2

Patterns compiled with Trivia runs faster than Optima.

runtime [sec]fibonaccigomokustring-match
optima11.539.882.5
trivia [1]9.6837.41.57

[1]: trivia is using :balland2006 optimiizer

… and Trivia is more extensible. In fact, Trivia’s defpattern is able to implement all of unmodifiable, core pattern language in Optima within itself.

(defpattern cons (a b)
  (with-gensyms (it)
    `(guard1 (,it :type cons) (consp ,it) (car ,it) ,a (cdr ,it) ,b)))

Detailed documentation is in github wiki.

Dependency & Testing

  • Level 0,1 : Alexandria only.
  • Level 2 : Additionally, lisp-namespace and closer-mop.

To run the tests, (asdf:test-system :trivia) .

To run the benchmark, (asdf:test-system :trivia.benchmark)

trivia's People

Contributors

binghe avatar daewok avatar dop avatar drmeister avatar ebrasca avatar fare avatar guicho271828 avatar m2ym avatar marcoheisig avatar mdbergmann avatar naryl avatar pfdietz avatar puercopop avatar remexre avatar rpgoldman avatar ruricolist avatar scymtym avatar sjl avatar y2q-actionman avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

trivia's Issues

setf-ing objects with let-match[1]

Is this a bug or working-as-designed?

CL-USER> (defstruct foo slot-1)
FOO
CL-USER> (defparameter f (make-foo))
F
CL-USER> (trivia:let-match1 (foo slot-1) f (setf slot-1 2))
2
CL-USER> (foo-slot-1 f)
NIL
CL-USER> (with-slots (slot-1) f (setf slot-1 2))
2
CL-USER> (foo-slot-1 f)
2

If working-as-designed, are there issues making let-match1 behave compatibility with with-slots or any design decisions?

Thanks!

License?

I've not been able to find anything in the sources dealing with licensing. Have I just not looked in the right place, or is it indeed absent? If so, is the implication that you are happy for any one to use this in any way they choose, or do you have thoughts on how you'd like people not to use it?

A hashmap pattern

As hash maps have really nice performance characteristics I use them quite a lot in my code. The support for hashmaps in trivia is not perfect, as I can't bind them in the pattern nor can I bind specific items of the hashmap by default. I have a pattern that can do both those things and I was wondering if you would be open to a PR containing such a pattern.

Style warning when matching structs on SBCL.

The following snippet of code produces a weird style warning on SBCL. (Both on 1.4.5 and 1.4.15):

(in-package #:cl-user)

(defstruct (foo (:predicate foop)))

(trivia:defpattern foo ()
  (let ((it (gensym)))
    `(trivia:guard1 ,it (foop ,it))))

(defun foo-finder (x)
  (trivia:match x
    ((foo) (format t "Found a foo!"))))

The style warning is

; in: defun foo-finder
; (TRIVIA.LEVEL2:MATCH X
; ((FOO) (FORMAT T "Found a foo!")))
; --> TRIVIA.LEVEL2:MATCH2 TRIVIA.LEVEL2:MATCH2+
; ==>
; (TRIVIA.LEVEL2:MATCH2*+ (X)
; (T)
; (((FOO)) (FORMAT T "Found a foo!"))
; ((TRIVIA.LEVEL2.IMPL::_) NIL))
;
; caught style-warning:
; undefined type: (foo)
;
; compilation unit finished
; Undefined type:
; (foo)
; caught 1 STYLE-WARNING condition

I only get this style warning with the latest Trivia release on Quicklisp, so it must have been due to a recent change.

There shall be only one!

Is there any reason not to just replace optima with trivia, then? (Assuming the optima author is willing.)

The (structure ...) example on the wiki spews warnings

I'm trying to use (structure ...) patterns but keep getting lots of warnings at macroexpansion time. I tried just running the bare example in the wiki and still get them:

><((°> rlwrap sbcl

[SBCL] CL-USER> (ql:quickload 'trivia)
To load "trivia":
  Load 1 ASDF system:
    trivia
; Loading "trivia"
(TRIVIA)

[SBCL] CL-USER> (use-package :trivia)
T

[SBCL] CL-USER> (defstruct foo bar baz)
FOO

[SBCL] CL-USER> (defvar *x* (make-foo :bar 0 :baz 1))
*X*

[SBCL] CL-USER> (match *x*
  ((foo :bar a :baz b) ;; make-instance style
   (values a b))
  ((foo (bar a) (baz b)) ;; with-slots style
   (values a b))
  ((foo bar baz) ;; slot name
   (values bar baz)))
WARNING:
   Calling #<FUNCTION FOO-BAR> failed, but not by program-error (TYPE-ERROR).
WARNING:
   Calling #<FUNCTION FOO-BAZ> failed, but not by program-error (TYPE-ERROR).
WARNING:
   Calling #<FUNCTION FOO-BAR> failed, but not by program-error (TYPE-ERROR).
WARNING:
   Calling #<FUNCTION FOO-BAZ> failed, but not by program-error (TYPE-ERROR).
WARNING:
   Calling #<FUNCTION FOO-BAR> failed, but not by program-error (TYPE-ERROR).
WARNING:
   Calling #<FUNCTION FOO-BAZ> failed, but not by program-error (TYPE-ERROR).

0
1

SBCL on OS X, if it matters. I'm using the latest Quicklisp dist.

Import #:split from :cl-ppcre

Please change the package definition of #:trivia.ppcre to,

(defpackage :trivia.ppcre
  (:export :ppcre
           :split
           :split*)
  (:import-from :cl-ppcre :split))

This removes symbol conflicts if/when one chooses to use symbols from both #:cl-ppcre and #:trivia.ppcre.

guard/or commutativity

The patterns guard/or appear to be used in 'commutative sense. For instance, the way I would read the below pattern is "find me variables that aren't x", however currently it returns '(the thing x) because the guard1 gets pushed inside the or1.

(match '(the thing x)
  ((guard (or (list 'the _ var) var) (not (eql var 'x))) var))

The relevant pattern-expansions are given below,

M> (pattern-expand-all '(or (list 'the _ var) var))
(OR1
 (GUARD1 (#:CONS2940 :TYPE CONS) (CONSP #:CONS2940) (CAR #:CONS2940)
  (GUARD1 (#:IT2941 :TYPE (EQL THE)) (EQ #:IT2941 'THE)) (CDR #:CONS2940)
  (GUARD1 (#:CONS2942 :TYPE CONS) (CONSP #:CONS2942) (CDR #:CONS2942)
   (GUARD1 (#:CONS2943 :TYPE CONS) (CONSP #:CONS2943) (CAR #:CONS2943)
    (GUARD1 VAR T) (CDR #:CONS2943)
    (GUARD1 (#:IT2944 :TYPE NULL) (NULL #:IT2944)))))
 (GUARD1 VAR T))
M> (pattern-expand-all '(guard (or (list 'the _ var) var) (not (eql var 'x))))
(OR1
 (GUARD1 #:INTERSECTION2947 T #:INTERSECTION2947
  (GUARD1 (#:CONS2946 :TYPE CONS) (CONSP #:CONS2946) (CAR #:CONS2946)
   (GUARD1 (#:IT2948 :TYPE (EQL THE)) (EQ #:IT2948 'THE)) (CDR #:CONS2946)
   (GUARD1 (#:CONS2949 :TYPE CONS) (CONSP #:CONS2949) (CDR #:CONS2949)
    (GUARD1 (#:CONS2950 :TYPE CONS) (CONSP #:CONS2950) (CAR #:CONS2950)
     (GUARD1 VAR T) (CDR #:CONS2950)
     (GUARD1 (#:IT2951 :TYPE NULL) (NULL #:IT2951))))
   #:INTERSECTION2947 (GUARD1 (#:GUARD2945 :DEFERRED (NOT (EQL VAR 'X))) T)))
 (GUARD1 #:INTERSECTION2952 T #:INTERSECTION2952
  (GUARD1 VAR T #:INTERSECTION2952
   (GUARD1 (#:GUARD2945 :DEFERRED (NOT (EQL VAR 'X))) T))))

Is this by design ? Could this behaviour be changed ?

Binding type/predicate pattern

I apologize if this isn't the right place to post this question!

I'm looking for a type predicate subpattern that also binds the value it's run on.

My use case is something like this: I want to only match lists that start with a string (or more generally, their first element satisfies some predicate) and also bind the first element of the list.

For simple patterns, something like this works:

(let ((x '("hello" 1))
  (match x
    ((list (type string) y) (cons (foo (car x)) (bar y))))

but ideally I'd like to not have to manually do the (car x).

The assoc pattern appears to mistakenly match anything at all, regardless of whether or not it should

The assoc pattern appears to mistakenly match anything at all. It only binds the variable when it should match, but still pretends it did match even when it shouldn't have with the variable bound to nil.

CL-USER> (values (machine-type) (machine-version) (software-type) (software-version)
                 (lisp-implementation-type) (lisp-implementation-version))
"x86_64"
"Intel(R) Core(TM) i7 CPU       M 620  @ 2.67GHz"
"Linux"
"4.4.0-31-generic"
"Clozure Common Lisp"
"Version 1.11-r16635  (LinuxX8664)"
CL-USER> (asdf:component-version (asdf:find-system :trivia nil))
"0.1"
CL-USER> (defun ft (x)
           (trivia:match x
             ((assoc :foo val) (list 'found val))))
FT
CL-USER> (ft '((:foo . 1)))
(FOUND 1)
CL-USER> (ft '((foo . 2)))
(FOUND NIL)
CL-USER> (ft '(("foo". 3)))
(FOUND NIL)
CL-USER> (ft '((0 . 4)))
(FOUND NIL)

Compare this to the behavior of Optima, which seems to get it right:

CL-USER> (asdf:component-version (asdf:find-system :optima nil))
"1.0"
CL-USER> (defun fo (x)
           (optima:match x
             ((assoc :foo val) (list 'found val))))
FO
CL-USER> (fo '((:foo . 1)))
(FOUND 1)
CL-USER> (fo '((foo . 2)))
NIL
CL-USER> (fo '(("foo". 3)))
NIL
CL-USER> (fo '((0 . 4)))
NIL

Trivia's atrophied on ABCL

Check the latest Travis results (e.g. #438.5) to see an UNBOUND-VARIABLE on load.

It might be a better solution to disable the CFFI tests for ABCL with #-abcl than to allow failures in general.

unification at level1 ?

I've often felt the need for a nice Prolog-ish DSL in CL. One limitation with implementations such as that in PAIP is that the pattern-matching is rather ad-hoc and not very satisfactory (in comparison to trivia). Adding some sort of unification for (level-1) patterns would make things very nice IMO.

I have been tinkering with level-1 definitions and while somethings are fairly straightforward, some are not. Things like unifying 'x and (list 1 2), where one of the patterns have to be reverse-engineered ala Prolog itself. I'm guessing however that the compiler itself is regular enough that handling this list-comprehension thing shouldn't be that difficult.

API unification on multiple values

Would it be possible to implement a values pattern?

(match (values 1 2)
  ((values 1 b) b))

Then all the multiple-value-* macros wouldn't be needed. Additionally this would work:

(let-match1 (values 1 b) (values 1 2) b)

Fix the compilation for read-time `structure-object` literal

My apologies if there is a mailing list or some such that's better suited than this for asking questions: I looked but failed to find one.

Anyway, I looked in the documentation, and failed to find an answer to this; my apologies if it's there and I just missed it.

When comparing constants what sort of equality is used? The following would seem to imply equal is being used:

CL-USER> (trivia:match "Foo"
           ("foo" :lower)
           ("FOO" :upper)
           ("Foo" :title))
:TITLE

So does this:

CL-USER> (trivia:match 1
           (1.0 :equalp)
           (1 :equal-or-eql))
:EQUAL-OR-EQL

(Note that in this implementation (CCL):

CL-USER> (list (equal 1 1.0) (equalp 1 1.0))
(NIL T)

)

But this seems to imply equalp is being used instead:

CL-USER> (trivia:match #(1 2 3)
           (#(1 2 3) t))
T

As does this:

CL-USER> (trivia:match #S(FROB :BLAH 1 :BLECH 2)
           (#S(FROB :BLAH 1 :BLECH 2) t))
T

Does it depend on the types involved? Of the thing being matched or of the pattern? And, if so, in which cases are what being used? Of, if it's something else, what, please? Or am I just confused, which is perfectly plausible.

TRIVIA does not load in CLISP due to a supposed misplaced declaration

stock CLISP on Debian Buster

;; Compiling file /home/r/quicklisp/dists/quicklisp/software/trivia-20210630-git/level2/impl.lisp ...
WARNING: RESTART-CASE: restart cannot be invoked interactively because it is missing a :INTERACTIVE option:
         (USE-VALUE (LISP-NAMESPACE::DEFAULT) (SETF (SYMBOL-PATTERN SYMBOL) LISP-NAMESPACE::DEFAULT))
WARNING: RESTART-CASE: restart cannot be invoked interactively because it is missing a :INTERACTIVE option:
         (USE-VALUE (LISP-NAMESPACE::DEFAULT) (SETF (SYMBOL-PATTERN SYMBOL) LISP-NAMESPACE::DEFAULT))
WARNING: RESTART-CASE: restart cannot be invoked interactively because it is missing a :INTERACTIVE option:
         (USE-VALUE (LISP-NAMESPACE::DEFAULT) (SETF (SYMBOL-INLINE-PATTERN SYMBOL) LISP-NAMESPACE::DEFAULT))
WARNING: RESTART-CASE: restart cannot be invoked interactively because it is missing a :INTERACTIVE option:
         (USE-VALUE (LISP-NAMESPACE::DEFAULT) (SETF (SYMBOL-INLINE-PATTERN SYMBOL) LISP-NAMESPACE::DEFAULT))
.
WARNING: RESTART-CASE: restart cannot be invoked interactively because it is missing a :INTERACTIVE option:
         (USE-VALUE (LISP-NAMESPACE::DEFAULT) (SETF (SYMBOL-PATTERN SYMBOL) LISP-NAMESPACE::DEFAULT))
WARNING: RESTART-CASE: restart cannot be invoked interactively because it is missing a :INTERACTIVE option:
         (USE-VALUE (LISP-NAMESPACE::DEFAULT) (SETF (SYMBOL-INLINE-PATTERN SYMBOL) LISP-NAMESPACE::DEFAULT))
WARNING: RESTART-CASE: restart cannot be invoked interactively because it is missing a :INTERACTIVE option:
         (USE-VALUE (LISP-NAMESPACE::DEFAULT) (SETF (SYMBOL-OPTIMIZER SYMBOL) LISP-NAMESPACE::DEFAULT))
WARNING: RESTART-CASE: restart cannot be invoked interactively because it is missing a :INTERACTIVE option:
         (USE-VALUE (LISP-NAMESPACE::DEFAULT) (SETF (SYMBOL-OPTIMIZER SYMBOL) LISP-NAMESPACE::DEFAULT))
WARNING: in #:|364 368 (TRIVIAL-CLTL2:DEFINE-DECLARATION OPTIMIZER (SPECIFIER ENV) ...)-31| in lines 364..368 : OPTIMIZER is neither declared nor bound,
         it will be treated as if it were declared SPECIAL.
WARNING: in #:|364 368 (TRIVIAL-CLTL2:DEFINE-DECLARATION OPTIMIZER (SPECIFIER ENV) ...)-31| in lines 364..368 : ENV is neither declared nor bound,
         it will be treated as if it were declared SPECIAL.
** - Continuable Error
in #:|364 368 (TRIVIAL-CLTL2:DEFINE-DECLARATION OPTIMIZER (SPECIFIER ENV) ...)-31| in lines 364..368 : Misplaced declaration: (DECLARE (IGNORABLE ENV))
If you continue (by typing 'continue'): Ignore the error and proceed
The following restarts are also available:
RETRY          :R1      Retry compiling #<CL-SOURCE-FILE "trivia.level2" "impl">.
ACCEPT         :R2      Continue, treating compiling #<CL-SOURCE-FILE "trivia.level2" "impl"> as having been successful.
RETRY          :R3      Retry ASDF operation.
CLEAR-CONFIGURATION-AND-RETRY :R4 Retry ASDF operation after resetting the configuration.
ABORT          :R5      Give up on "trivia"
REGISTER-LOCAL-PROJECTS :R6 Register local projects and try again.
ABORT          :R7      Abort main loop

compile fails on ECL-Android

Using git head Trivia on ECL-Android with the new (progn (signal 'wildcard)) fix, but behavior is unchanged and still signals during compilation.

(asdf:load-system :trivia)
.........
.........
;;; Compiling input stream /data/data/org.lisp.ecl/app_resources/home/quicklisp/local-projects/trivia/level2/derived3.lisp

[Condition of type TRIVIA.LEVEL2.IMPL::WILDCARD]

Patterns with quote broken on Allegro

CG-USER(3): (trivia:match 'x ('x t))
Error: attempt to call `NIL' which is an undefined function.
[condition type: UNDEFINED-FUNCTION]

The bug is in the expansion, not the macro itself.

String pattern matching is more strict than STRING=

Trivia does not think that a vector of characters matches a string, even though STRING= says they're equal. This behavior is counter-intuitive. For example:

CL-USER> (defvar vec (make-array 3 :adjustable t :initial-contents "abc" :element-type 'character))
VEC
CL-USER> vec
"abc"
CL-USER> (string= vec "abc")
T
CL-USER> (type-of vec)
(VECTOR CHARACTER 3)
CL-USER> (type-of "abc")
(SIMPLE-ARRAY CHARACTER (3))
CL-USER> (match vec 
           ("abc" 'yes)
           (_ 'no))
NO

What would you guys think about changing this behavior so that VEC matches "abc"?

Bug with property

I expect this to return 88 but it returns NIL.

(match '(:y 88)
  ((property :x x) x)
  ((property :y y) y))

Feature request: docstring support for `defun-match`

It would be nice if defun-match could optionally take a docstring and pass it along into the underlying defun. Right now it tries to parse the string as a match clause and errors.

According to the docs the clauses in the body are always lists, so it should be possible to distinguish a bare string and treat it separately.

If this is something you're interested in I can make a PR for it.

Use of otherwise pattern in CCL results in spurious unused lexical variable warning

CL-USER> (values (machine-type) (machine-version) (software-type) (software-version)
                 (lisp-implementation-type) (lisp-implementation-version))
"x86_64"
"Intel(R) Core(TM) i7 CPU       M 620  @ 2.67GHz"
"Linux"
"4.4.0-31-generic"
"Clozure Common Lisp"
"Version 1.11-r16635  (LinuxX8664)"
CL-USER> (asdf:component-version (asdf:find-system :trivia nil))
"0.1"
CL-USER> (defun f (x)
           (trivia:match x
             ((list 1 z) z)
             (otherwise :nope)))
;Compiler warnings :
;   In F: Unused lexical variable OTHERWISE
F
CL-USER> ; demonstrate that it works right, it's just a spurious warning
; No value
CL-USER> (f '(1 2))
2
CL-USER> (f '(1 2 3))
:NOPE
CL-USER> ; this is Ubuntu 16.04
; No value
CL-USER> 

Guard pattern doesn't bind variables on successful match

Hi, when evaluating

(trivia:ematch '(shader foo :fragment "")
  ((trivia:guard (list shader name type value)
                 (string-equal (symbol-name shader) "shader"))
   (list name type value)))

I get

The variable SHADER is unbound.
   [Condition of type UNBOUND-VARIABLE]

In optima it works

(optima:ematch '(shader foo :fragment "")
  ((optima:guard (list shader name type value)
                 (string-equal (symbol-name shader) "shader"))
   (list name type value)))

Am I miss using the guard subpattern?

Control stack exhausted when expanding match body with strings

I don't know if this is a bug or if I am doing something wrong. I have the following function:

(defun prefix-type-cast (cast operand &optional (start 0))
  "Perform a compile-time type cast using a prefixed qualifier. Used
in conjunction with the \"^^\" operator."
  (cond
    ((or (string= cast "http://www.w3.org/2001/XMLSchema#integer")
         (string= cast "http://www.w3.org/2001/XMLSchema#long"))
     (make-ruleml-number :value (parse-integer operand)
                         :position start))
    ((string= cast "http://www.w3.org/2001/XMLSchema#double")
     (make-ruleml-number :value (read-from-string operand)
                         :position start))
    ((string= cast "http://www.w3.org/2001/XMLSchema#string")
     (make-ruleml-string :contents operand
                         :position start))))

which I would much rather write using match:

(defun prefix-type-cast (cast operand &optional (start 0))
  "Perform a compile-time type cast using a prefixed qualifier. Used
in conjunction with the \"^^\" operator."
  (match cast
    ((or "http://www.w3.org/2001/XMLSchema#integer"
         "http://www.w3.org/2001/XMLSchema#long")
     (make-ruleml-number :value (parse-integer operand)
                         :position start))
    ("http://www.w3.org/2001/XMLSchema#double"
     (make-ruleml-number :value (read-from-string operand)
                         :position start))
    ("http://www.w3.org/2001/XMLSchema#string"
     (make-ruleml-string :contents operand
                         :position start))))

When I try to compile it, the control stack is exhausted. This is the backtrace from SBCL:

Control stack exhausted (no more space for function call frames).
This is probably due to heavily nested or infinitely recursive function
calls, or a tail call that SBCL cannot or has not optimized away.

PROCEED WITH CAUTION.
   [Condition of type SB-KERNEL::CONTROL-STACK-EXHAUSTED]

Restarts:
 0: [ABORT] Abort compilation.
 1: [*ABORT] Return to SLIME's top level.
 2: [ABORT] abort thread (#<THREAD "worker" RUNNING {1001A80FD3}>)

Backtrace:
  0: (SB-KERNEL::CONTROL-STACK-EXHAUSTED-ERROR)
  1: ("foreign function: call_into_lisp")
  2: ("foreign function: post_signal_tramp")
  3: ((LABELS SB-IMPL::S :IN SUBST) (#\a))
  4: ((LABELS SB-IMPL::S :IN SUBST) (EQL #\a))
  5: ((LABELS SB-IMPL::S :IN SUBST) ((EQL #\a)))
  6: ((LABELS SB-IMPL::S :IN SUBST) (:TYPE (EQL #\a)))
  7: ((LABELS SB-IMPL::S :IN SUBST) (LET :TYPE (EQL #\a)))
  8: ((LABELS SB-IMPL::S :IN SUBST) (:BINDER LET :TYPE (EQL #\a)))
  9: ((LABELS SB-IMPL::S :IN SUBST) (T :BINDER LET :TYPE (EQL #\a)))
 10: ((LABELS SB-IMPL::S :IN SUBST) (:IGNORABLE T :BINDER LET :TYPE (EQL #\a)))
 11: ((LABELS SB-IMPL::S :IN SUBST) (NIL :IGNORABLE T :BINDER LET :TYPE ...))
 12: ((LABELS SB-IMPL::S :IN SUBST) (:DYNAMIC-EXTENT NIL :IGNORABLE T :BINDER LET ...))
 13: ((LABELS SB-IMPL::S :IN SUBST) (NIL :DYNAMIC-EXTENT NIL :IGNORABLE T :BINDER ...))
 14: ((LABELS SB-IMPL::S :IN SUBST) (:SPECIAL NIL :DYNAMIC-EXTENT NIL :IGNORABLE T ...))
 15: ((LABELS SB-IMPL::S :IN SUBST) (#:IT112 :SPECIAL NIL :DYNAMIC-EXTENT NIL :IGNORABLE ...))
 16: ((LABELS SB-IMPL::S :IN SUBST) ((#1=#:IT112 :SPECIAL NIL :DYNAMIC-EXTENT NIL :IGNORABLE ...) (EQL #1# #\a)))
 17: ((LABELS SB-IMPL::S :IN SUBST) (GUARD1 (#1=#:IT112 :SPECIAL NIL :DYNAMIC-EXTENT NIL :IGNORABLE ...) (EQL #1# #\a)))
 18: ((LABELS SB-IMPL::S :IN SUBST) ((GUARD1 (#1=#:IT112 :SPECIAL NIL :DYNAMIC-EXTENT NIL :IGNORABLE ...) (EQL #1# #\a)) (GUARD1 (#2=#:IT113 :SPECIAL NIL :DYNAMIC-EXTENT NIL :IGNORABLE ...) (EQL #2# #\#)) ..
 19: ((LABELS SB-IMPL::S :IN SUBST) ((GUARD1 (#1=#:IT111 :SPECIAL NIL :DYNAMIC-EXTENT NIL :IGNORABLE ...) (EQL #1# #\m)) (GUARD1 (#2=#:IT112 :SPECIAL NIL :DYNAMIC-EXTENT NIL :IGNORABLE ...) (EQL #2# #\a)) ..
 --more--

binary-search based keyword parsing

I was playing with the binary-search parser for keywords; it looks like the overhead of dealing with the array store makes such an approach very slow compared to using property (by an order of magnitude). It seems really strange that that'd be true.

@guicho271828 is there something I'm doing wrong here ?

(in-package :trivia.level2.impl)

(defun compile-destructuring-pattern (ops &optional default)
  (match ops
    (nil default)
    ((list* (list :whole subpattern) rest)
     `(and ,subpattern ,(compile-destructuring-pattern rest)))
    ((list* (list* :atom subpatterns) rest)
     `(list* ,@subpatterns ,(compile-destructuring-pattern rest)))
    ((list* (list :optional) rest)
     (compile-destructuring-pattern rest))
    ((list* (list* :optional subpattern more-subpatterns) rest)
     (with-gensyms (lst supplied-p-default-sym)
       (destructuring-bind (subpattern &optional default (supplied-p-pattern supplied-p-default-sym supplied-p-pattern-supplied)) subpattern
         `(guard1 (,lst :type list) (listp ,lst)
                  (if ,lst (car ,lst) ,default) ,subpattern
                  ,@(when supplied-p-pattern-supplied
                      `((if ,lst t nil) ,supplied-p-pattern))
                  (cdr ,lst) ,(compile-destructuring-pattern `((:optional ,@more-subpatterns) ,@rest))))))
    ((list* (list :rest pattern) rest)
     `(and ,pattern ,(compile-destructuring-pattern rest '_)))
    ((list* (list* (and mode (or :keyword (list :keyword-allow-other-keys rem))) subpatterns) rest)
     ;; case 1,2 of the &key forms are already compiled into the 3rd form ; see parse-lambda-list
     `(and (type list)
           ;; sequentially accumulate keys
       ,(optimized-key-access (if (eq mode :keyword) nil (or rem '_)) subpatterns)
           ;; compile the rest
           ,(compile-destructuring-pattern rest '_)))
    ((list (list* :aux subpatterns))
     `(guard1 ,(gensym) t ,@(mapcan #'(lambda (x)
                                        (destructuring-bind (var &optional expr) (ensure-list x)
                                          (assert (typep var 'variable-symbol) nil "invalid lambda list")
                                          `(,expr ,var)))
                                    subpatterns)))))

(defun optimized-key-access (remainder-pattern subpatterns)
  ;; NOTE: uses a binary heap (instead) to achieve O(n lg n) speed using a single pass
  (let* ((props (compile-keyword-patterns subpatterns))
     (skeys (sort (mapcar #'second props) #'string<)))
    (with-gensyms (lst kargs indicator)
      `(guard1 ,lst t
           (let ((,kargs (make-array ,(length skeys) :element-type 'keyword)))
         (declare (type (simple-array t (*)) ,kargs))
         ;;,@(loop :for ii :below (length skeys) :collect `(setf (aref ,kargs ,ii) ',indicator))
         ,kargs) ,kargs
         ;;(kargs-parse nil #+nil',indicator ,lst #(,@skeys) ,kargs ,(if (eql remainder-pattern '_) nil t)) (list ,remainder-pattern nil)
        ,@(mapcan #'(lambda (x)
                 (destructuring-bind (key subpattern default &optional (supplied-p-pattern nil supplied-p-pattern-suppliedp)) (cdr x)
                   (let ((pos (position key skeys)))
                 `((if (eql (aref ,kargs ,pos) ',indicator) ,default (aref ,kargs ,pos)) ,subpattern
                   ,@(if supplied-p-pattern-suppliedp
                     `((if (eql (aref ,kargs ,pos) ',indicator) nil t) ,supplied-p-pattern))))))
             props)))))

(declaim (inline kargs-parse))
(defun kargs-parse (indicator lst heap kargs &optional collect &aux rest)
  (declare (type (simple-array keyword (*)) heap)
       (type (simple-array t (*)) kargs)
       (type symbol indicator)
       (optimize (speed 3) (safety 0)))
  (list
   (loop :for (k v . r) :on lst :by #'cddr
      :while (keywordp k)
      :for pos := (binary-search k 0 (length heap) heap)
      :if pos :do (if (eql (aref kargs pos) indicator) (setf (aref kargs pos) v))
      :else :if collect :collect k :and :collect v
      :do (setf rest r))
   rest))

(declaim (inline binary-search))
(defun binary-search (val lb ub vec)
  (declare (type fixnum lb ub)
       (type keyword val)
       (type (simple-array keyword (*)) vec))
  (cond
    ((or (= lb ub) (string< val (aref vec lb))) nil)
    ((string< (aref vec (1- ub)) val) nil)
    (t (loop :for j :of-type fixnum := (floor (+ lb ub) 2)
      :repeat #.(ceiling (log array-dimension-limit 2))
      :do (cond ((string= (aref vec j) val) (return j))
            ((>= lb (1- ub)) (return nil))
            (t (if (string< val (aref vec j))
               (setf ub j)
               (setf lb (1+ j)))))))))

Dynamically generate a pattern matcher depending on some value

(match '(0 . 1)
  ((list* x _)
   (match 2
     (x `(x-previously-matched-is-invisible (x = ,x)))
     (_ 'x-previously-matched-to-0-is-visible))))
=>
(X-PREVIOUSLY-MATCHED-IS-INVISIBLE (X = 2))

I believe it's natural to rather have internal x bound to 0 in this case.

Is there a reason to not inherit bindings in nested match forms?

Add Optima's Extra Functions

I think it would be nice to have optima's extra functions. Trivia has the lambda-match functions, but I don't see if-match, when-match, let-match, etc. I think let-match is especially useful and extends optima to be able to be used in much the same way as metabang-bind.

Taking an idea from metabang bind, it might also be nice to be able to match slots with their accessors. Also, I was wondering if it would be possible to have a values pattern or is multiple-value-match a necessity?

Spurious message when loading trivia

When loading trivia, the spurious message "Switching to the BALLAND2006 optimizer" is displayed. Maybe this should only be displayed when *asdf-verbose* is non-NIL? or something?

Surprising `list*` behavior

I was trying to match the contents of a list to do something with it, like this:

(match foo
  ; if foo is a list, transform its contents
  ((list* contents) (mapcar #'whatever contents))
  ; otherwise...
)

But it appears that list* with a single argument will just match anything at all:

(match 'x ((list* foo) foo))
X

The docs in the wiki for list and list* say:

Both patterns checks if the object is of type list

so this seems like a bug in either the matcher or the docs...

no-applicable-method for mop:compute-slots on structure classes in ABCL

I'm trying to load my project that uses trivia into ABCL through asdf, and I get a no-applicable-method error for mop:compute-slots, with backtrace:

Backtrace:
  0: (#<FUNCTION {6E17A35E}> #<SIMPLE-ERROR {5F040AF6}> #<FUNCTION {6E17A35E}>)
  1: (APPLY #<FUNCTION {6E17A35E}> (#<SIMPLE-ERROR {5F040AF6}> #<FUNCTION {6E17A35E}>))
  2: (SYSTEM::RUN-HOOK SYSTEM::*INVOKE-DEBUGGER-HOOK* #<SIMPLE-ERROR {5F040AF6}> #<FUNCTION {6E17A35E}>)
  3: (INVOKE-DEBUGGER #<SIMPLE-ERROR {5F040AF6}>)
  4: (ERROR "There is no applicable method for the generic function ~S when called with arguments ~S." #<STANDARD-GENERIC-FUNCTION {A199C6}> (#<STRUCTURE-CLASS RULEML-DOCUMENT>))
  5: (NO-APPLICABLE-METHOD #<STANDARD-GENERIC-FUNCTION {A199C6}> #<STRUCTURE-CLASS RULEML-DOCUMENT>)
  6: (APPLY #<NO-APPLICABLE-METHOD {38C58F05}> #<STANDARD-GENERIC-FUNCTION {A199C6}> (#<STRUCTURE-CLASS RULEML-DOCUMENT>))
      Locals:
        EXTENSIONS::|function| = #<FUNCTION #<NO-APPLICABLE-METHOD {38C58F05}> {38C58F05}>
        EXTENSIONS::|&rest|#1 = #<STANDARD-GENERIC-FUNCTION MOP:COMPUTE-SLOTS {A199C6}>
        EXTENSIONS::|args|#2 = (#<STRUCTURE-CLASS RULEML-DOCUMENT {6D5EA260}>)
  7: (MOP:COMPUTE-SLOTS #<STRUCTURE-CLASS RULEML-DOCUMENT>)
      Locals:
        "arg0" = #<STRUCTURE-CLASS RULEML-DOCUMENT {6D5EA260}>
  8: (TRIVIA.LEVEL2.IMPL::FIND-EFFECTIVE-SLOT :BASE RULEML-DOCUMENT)
      Locals:
        SYMBOL = :BASE
        TYPE#1 = RULEML-DOCUMENT
  9: (TRIVIA.LEVEL2.IMPL::ACCESSOR-FORM-ON-STRUCTURE #:IT315038 RULEML-DOCUMENT (:BASE BASE))
 10: (#<FUNCTION {4DBE843E}> (:BASE BASE))
 11: (MAPCAR #<FUNCTION {4DBE843E}> ((:BASE BASE) (:PREFIXES PREFIXES) (:IMPORTS IMPORTS) (:PERFORMATIVES PERFORMATIVES)))
 12: (APPLY #<MAPCAR {5F956734}> #<FUNCTION {4DBE843E}> (((:BASE BASE) (:PREFIXES PREFIXES) (:IMPORTS IMPORTS) (:PERFORMATIVES PERFORMATIVES))))
 13: (ALEXANDRIA:MAPPEND #<FUNCTION {4DBE843E}> ((:BASE BASE) (:PREFIXES PREFIXES) (:IMPORTS IMPORTS) (:PERFORMATIVES PERFORMATIVES)))
 14: (TRIVIA.LEVEL2.IMPL::MAP-ACCESSORS ((:BASE BASE) (:PREFIXES PREFIXES) (:IMPORTS IMPORTS) (:PERFORMATIVES PERFORMATIVES)) #:IT315038 RULEML-DOCUMENT)
 15: (#<FUNCTION {766F1D9A}> RULEML-DOCUMENT :BASE BASE :PREFIXES PREFIXES ...)
 16: (APPLY #<FUNCTION {766F1D9A}> (RULEML-DOCUMENT :BASE BASE :PREFIXES PREFIXES :IMPORTS ...))
 17: (PATTERN-EXPAND-1 (STRUCTURE RULEML-DOCUMENT :BASE BASE :PREFIXES PREFIXES ...))
 18: (PATTERN-EXPAND (RULEML-DOCUMENT :BASE BASE :PREFIXES PREFIXES :IMPORTS ...))
 19: (PATTERN-EXPAND-ALL (RULEML-DOCUMENT :BASE BASE :PREFIXES PREFIXES :IMPORTS ...))
 20: (TRIVIA.LEVEL2.IMPL::PATTERN-EXPAND-ALL/LIFT0 (RULEML-DOCUMENT :BASE BASE :PREFIXES PREFIXES :IMPORTS ...))
 21: (TRIVIA.LEVEL2.IMPL::PATTERN-EXPAND-ALL/LIFT (RULEML-DOCUMENT :BASE BASE :PREFIXES PREFIXES :IMPORTS ...))
 22: (TRIVIA.LEVEL2.IMPL::EXPAND-MULTIPATTERNS ((RULEML-DOCUMENT :BASE BASE :PREFIXES PREFIXES :IMPORTS ...)))
 23: (TRIVIA.LEVEL2.IMPL::EXPAND-CLAUSE (((RULEML-DOCUMENT :BASE BASE :PREFIXES PREFIXES :IMPORTS ...)) (FUNCALL KEY (MAKE-RULEML-DOCUMENT :BASE # :PREFIXES # :IMPORTS ...))))
 24: ((MACRO-FUNCTION MATCH2*+) (MATCH2*+ (TERM) (T) ((#) (FUNCALL KEY #)) ((#) (FUNCALL KEY # :POSITIVE POSITIVE :NEGATIVE ...)) ((#) (FUNCALL KEY # :POSITIVE POSITIVE :NEGATIVE ...)) ...) #<ENVIRONMENT {..
 25: (MACROEXPAND-1 (MATCH2*+ (TERM) (T) ((#) (FUNCALL KEY #)) ((#) (FUNCALL KEY # :POSITIVE POSITIVE :NEGATIVE ...)) ((#) (FUNCALL KEY # :POSITIVE POSITIVE :NEGATIVE ...)) ...) #<ENVIRONMENT {68F9116F}>)
 26: (PRECOMPILER::PRECOMPILE1 (MATCH2*+ (TERM) (T) ((#) (FUNCALL KEY #)) ((#) (FUNCALL KEY # :POSITIVE POSITIVE :NEGATIVE ...)) ((#) (FUNCALL KEY # :POSITIVE POSITIVE :NEGATIVE ...)) ...))
 27: (PRECOMPILER::PRECOMPILE1 (MATCH2+ TERM T ((RULEML-DOCUMENT :BASE BASE :PREFIXES PREFIXES :IMPORTS ...) (FUNCALL KEY #)) ((RULEML-ASSERT :ITEMS TERMS) (FUNCALL KEY # :POSITIVE POSITIVE :NEGATIVE ...))..
 28: (PRECOMPILER::PRECOMPILE1 (MATCH2 TERM ((RULEML-DOCUMENT :BASE BASE :PREFIXES PREFIXES :IMPORTS ...) (FUNCALL KEY #)) ((RULEML-ASSERT :ITEMS TERMS) (FUNCALL KEY # :POSITIVE POSITIVE :NEGATIVE ...)) ((..
 29: (PRECOMPILER::PRECOMPILE1 (MATCH TERM ((RULEML-DOCUMENT :BASE BASE :PREFIXES PREFIXES :IMPORTS ...) (FUNCALL KEY #)) ((RULEML-ASSERT :ITEMS TERMS) (FUNCALL KEY # :POSITIVE POSITIVE :NEGATIVE ...)) ((R..
 30: (PRECOMPILER::PRECOMPILE-FLET/LABELS (FLET ((DEFAULT-PROPAGATOR # #)) (MATCH TERM (# #) (# #) (# #) (# #) ...)))
 31: (PRECOMPILER::PRECOMPILE1 (FLET ((DEFAULT-PROPAGATOR # #)) (MATCH TERM (# #) (# #) (# #) (# #) ...)))
 32: (PRECOMPILER::PRECOMPILE-BLOCK (BLOCK TRANSFORM-AST (FLET (#) (MATCH TERM # # # # ...))))
 33: (PRECOMPILER::PRECOMPILE1 (BLOCK TRANSFORM-AST (FLET (#) (MATCH TERM # # # # ...))))
 34: (PRECOMPILER::PRECOMPILE-LAMBDA (LAMBDA (TERM KEY &KEY POSITIVE NEGATIVE EXTERNAL ...) (BLOCK TRANSFORM-AST (FLET # #))))
 35: (PRECOMPILER::PRECOMPILE1 (LAMBDA (TERM KEY &KEY POSITIVE NEGATIVE EXTERNAL ...) (BLOCK TRANSFORM-AST (FLET # #))))
 36: (JVM:COMPILE-DEFUN TRANSFORM-AST (LAMBDA (TERM KEY &KEY POSITIVE NEGATIVE EXTERNAL ...) (BLOCK TRANSFORM-AST (FLET # #))) NIL #P"/home/mark/Projects/CL/PSOATransRun/psoa_ast_480.cls" #<FILE-STREAM {17..
 37: (SYSTEM::PROCESS-TOPLEVEL-DEFUN (DEFUN TRANSFORM-AST (TERM KEY &KEY POSITIVE NEGATIVE EXTERNAL ...) "Performs a post-order traversal of an abstract syntax tree of PSOA
     RuleML nodes, all of which have ..
 38: (SYSTEM::PROCESS-TOPLEVEL-FORM (DEFUN TRANSFORM-AST (TERM KEY &KEY POSITIVE NEGATIVE EXTERNAL ...) "Performs a post-order traversal of an abstract syntax tree of PSOA
     RuleML nodes, all of which have s..
 39: (JVM::%WITH-COMPILATION-UNIT #<FUNCTION {7DAD4A00}>)
 40: (SYSTEM::COMPILE-FROM-STREAM #<FILE-STREAM {5DFF5EB3}> #P"/home/mark/Projects/CL/PSOATransRun/psoa-ast.abcl" #P"/home/mark/Projects/CL/PSOATransRun/psoa-ast.abcl-tmp" #P"/home/mark/Projects/CL/PSOATra..
 41: (COMPILE-FILE #P"/home/mark/Projects/CL/PSOATransRun/psoa-ast.lisp" :OUTPUT-FILE #P"/home/mark/Projects/CL/PSOATransRun/psoa-ast.abcl")
 42: (#<FUNCTION (LAMBDA ()) {653B2C35}>)
 43: (JAVA:JRUN-EXCEPTION-PROTECTED #<FUNCTION (LAMBDA ()) {653B2C35}>)
 44: ((FLET SWANK/BACKEND:SWANK-COMPILE-FILE) #P"/home/mark/Projects/CL/PSOATransRun/psoa-ast.lisp" #P"/home/mark/Projects/CL/PSOATransRun/psoa-ast.abcl" NIL :DEFAULT :POLICY ...)
 45: (APPLY #<(FLET SWANK-COMPILE-FILE) {7CE71428}> #P"/home/mark/Projects/CL/PSOATransRun/psoa-ast.lisp" #P"/home/mark/Projects/CL/PSOATransRun/psoa-ast.abcl" NIL :DEFAULT ...)
 46: (SWANK/BACKEND:SWANK-COMPILE-FILE #P"/home/mark/Projects/CL/PSOATransRun/psoa-ast.lisp" #P"/home/mark/Projects/CL/PSOATransRun/psoa-ast.abcl" NIL :DEFAULT :POLICY ...)
 47: (SWANK::SWANK-COMPILE-FILE* #P"/home/mark/Projects/CL/PSOATransRun/psoa-ast.lisp" T)
 48: (APPLY SWANK::SWANK-COMPILE-FILE* #P"/home/mark/Projects/CL/PSOATransRun/psoa-ast.lisp" T NIL)
 49: (#<FUNCTION {6B0DACFE}>)
 50: (#<FUNCTION {4CA06DEA}>)
 51: (SWANK::MEASURE-TIME-INTERVAL #<FUNCTION {4CA06DEA}>)
 52: (SWANK::COLLECT-NOTES #<FUNCTION {6B0DACFE}>)
 53: (#<FUNCTION {70C6AACF}>)
 54: (RUTILS.ABBR:CALL #<FUNCTION {70C6AACF}>)
 55: (#<FUNCTION (LAMBDA (SWANK/BACKEND::FN)) {48401CAD}> #<FUNCTION {70C6AACF}>)
 56: (APPLY #<FUNCTION (LAMBDA (SWANK/BACKEND::FN)) {48401CAD}> #<FUNCTION {70C6AACF}> NIL)
 57: (SWANK/BACKEND:CALL-WITH-SYNTAX-HOOKS #<FUNCTION {70C6AACF}>)
 58: (SWANK::CALL-WITH-BUFFER-SYNTAX NIL #<FUNCTION {70C6AACF}>)
 59: (SWANK:COMPILE-FILE-FOR-EMACS "/home/mark/Projects/CL/PSOATransRun/psoa-ast.lisp" T)
 60: (SYSTEM::%EVAL (SWANK:COMPILE-FILE-FOR-EMACS "/home/mark/Projects/CL/PSOATransRun/psoa-ast.lisp" T))
 61: (EVAL (SWANK:COMPILE-FILE-FOR-EMACS "/home/mark/Projects/CL/PSOATransRun/psoa-ast.lisp" T))
 62: (SWANK:EVAL-FOR-EMACS (SWANK:COMPILE-FILE-FOR-EMACS "/home/mark/Projects/CL/PSOATransRun/psoa-ast.lisp" T) "#:psoa-ast" 83)
 63: (APPLY #<EVAL-FOR-EMACS {C887C6A}> ((SWANK:COMPILE-FILE-FOR-EMACS "/home/mark/Projects/CL/PSOATransRun/psoa-ast.lisp" T) "#:psoa-ast" 83))
 64: (#<FUNCTION {34C4A6AB}>)
 65: (RUTILS.ABBR:CALL #<FUNCTION {34C4A6AB}>)
 66: ((FLET SWANK/BACKEND:CALL-WITH-DEBUGGER-HOOK) #<SWANK-DEBUGGER-HOOK {6952175E}> #<FUNCTION {34C4A6AB}>)
 67: (APPLY #<(FLET CALL-WITH-DEBUGGER-HOOK) {32A88691}> #<SWANK-DEBUGGER-HOOK {6952175E}> #<FUNCTION {34C4A6AB}> NIL)
 68: (SWANK/BACKEND:CALL-WITH-DEBUGGER-HOOK #<SWANK-DEBUGGER-HOOK {6952175E}> #<FUNCTION {34C4A6AB}>)
 69: (#<FUNCTION {7DA86213}>)
 70: (SWANK::CALL-WITH-BINDINGS ((*STANDARD-INPUT* . #S(EXTENSIONS:SLIME-INPUT-STREAM)) (*STANDARD-OUTPUT* . #S(EXTENSIONS:SLIME-OUTPUT-STREAM)) (*TRACE-OUTPUT* . #S(EXTENSIONS:SLIME-OUTPUT-STREAM)) (*ERRO..
 71: (#<FUNCTION {299D37F1}>)
 72: (SWANK::CALL-WITH-BINDINGS NIL #<FUNCTION {299D37F1}>)
 73: (#<FUNCTION {5FF7A05D}>)
 74: (RUTILS.ABBR:CALL #<FUNCTION {5FF7A05D}>)
 75: (#<FUNCTION (LAMBDA ()) {6171F94A}>)
 76: (THREADS::THREAD-FUNCTION-WRAPPER #<FUNCTION (LAMBDA ()) {6171F94A}>)

when compiling this file: https://github.com/mthom/cl-psoatransrun/blob/master/psoa-ast.lisp

guard example from the wiki: invalid number of arguments

Hello,

This example:

(match (list 2 5)
  ((guard (list x y)     ; subpattern1
          (= 10 (* x y)) ; test-form
          (- x y) (satisfies evenp)) ; generator-form, subpattern2
   t))

from https://github.com/guicho271828/trivia/wiki/Logic-Based-Patterns

throws:

invalid number of arguments: 4
   [Condition of type SB-INT:SIMPLE-PROGRAM-ERROR]

Restarts:
 0: [REPLACE-FUNCTION] Call a different function with the same arguments
 1: [CALL-FORM] Call a different form
 2: [RETRY] Retry SLIME REPL evaluation request.
 3: [*ABORT] Return to SLIME's top level.
 4: [ABORT] abort thread (#<THREAD "repl-thread" RUNNING {1001BE1B63}>)

Backtrace:
  0: ((QUOTE GUARD) (LIST X Y) (= 10 (* X Y)) (- X Y) (SATISFIES EVENP)) [external]
  1: (TRIVIA.LEVEL2:PATTERN-EXPAND-1 (GUARD (LIST X Y) (= 10 (* X Y)) (- X Y) (SATISFIES EVENP)))
  2: (TRIVIA.LEVEL2:PATTERN-EXPAND (GUARD (LIST X Y) (= 10 (* X Y)) (- X Y) (SATISFIES EVENP)))
  3: (TRIVIA.LEVEL2:PATTERN-EXPAND-ALL (GUARD (LIST X Y) (= 10 (* X Y)) (- X Y) (SATISFIES EVENP)))
  4: (TRIVIA.LEVEL2.IMPL::PATTERN-EXPAND-ALL/LIFT0 (GUARD (LIST X Y) (= 10 (* X Y)) (- X Y) (SATISFIES EVENP)))
  5: (TRIVIA.LEVEL2.IMPL::PATTERN-EXPAND-ALL/LIFT (GUARD (LIST X Y) (= 10 (* X Y)) (- X Y) (SATISFIES EVENP)))
  6: (TRIVIA.LEVEL2.IMPL::EXPAND-MULTIPATTERNS ((GUARD (LIST X Y) (= 10 #) (- X Y) (SATISFIES EVENP))))
  7: (TRIVIA.LEVEL2.IMPL::EXPAND-CLAUSE (((GUARD # # # #)) T))
  8: ((MACRO-FUNCTION TRIVIA.LEVEL2:MATCH2*+) (TRIVIA.LEVEL2:MATCH2*+ ((LIST 2 5)) (T) ((#) T) ((TRIVIA.LEVEL2.IMPL::_) NIL)) #<NULL-LEXENV>)
  9: ((FLET SB-IMPL::PERFORM-EXPANSION :IN MACROEXPAND-1) #<FUNCTION (MACRO-FUNCTION TRIVIA.LEVEL2:MATCH2*+) {22F466EB}> NIL)
 10: (MACROEXPAND (MATCH (LIST 2 5) ((GUARD # # # #) T)) #<NULL-LEXENV>)

How should it be fixed?

Best,

SBCL 1.4.5-debian, QL dist "2020-12-20"

Stack overflow when loading trivia in ABCL

Trying to (ql:quickload 'trivia) in ABCL on OS X somehow manages to blow the stack:

https://gist.github.com/sjl/16fac0bdb422e1fd1cc485ffbce6a0d5

(adsf:load-system 'trivia :verbose t) doesn't give any addition useful information.

I've narrowed down the problem to docparser -- (ql:quickload 'docparser) is what's blowing up the stack. So I figured I could depend on trivia.level2 instead, which shouldn't require docparser. But for some reason (ql:quickload 'trivia.level2) still fails with the same problem even though it doesn't seem to be loading docparser (at least as far as I can tell from reading the .asd file).

I'm just gonna use optima for now, but I figured I'd file the issue just in case someone knows how to fix things.

PPCRE matcher to work on symbols

Hi,
This is a feature request. Currently the ppcre matcher only works on literal strings, would it be possible to treat symbols as potential variables?

For example

(let ((url-regexp "^/user/(\\w+/$)"))
  (match "/user/1/"
    ((ppcre url-regexp user-id) user-id)))

complains that url-regexp is not of type string. Being able to associate regexps with names that describe their intent is useful from a development experience point of view, even if at odds with efficiency.

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.