Git Product home page Git Product logo

serapeum's Introduction

Table of Contents

Overview

CI

Serapeum is a conservative library of Common Lisp utilities. It is a supplement, not a competitor, to Alexandria. That means it is safe to do:

(defpackage ... (:use #:cl #:alexandria #:serapeum),

without package conflicts.

Alternatively, now that package-local nicknames are generally available, the serapeum/bundle package reexports the symbols of both (along with other utilities used by Serapeum itself):

(defpackage ... (:local-nicknames (:util :serapeum/bundle)))

There may already be too many utility libraries for Common Lisp. Releasing another has become something to apologize for, not celebrate. But I would rather make my apologies than have to maintain copy-pasted versions of the same utilities across a dozen systems. And, though Serapeum is justified even if only I ever use it, the best way to ensure its quality is to write it as if for general use.

Serapeum is conservative: its goal is to fill in gaps in Common Lisp, not to redesign it. But it is less conservative than Alexandria. Alexandria limits itself to utilities with a Common Lisp pedigree. Serapeum casts a wider net: other dialects of Lisp, and other languages in the functional and array families, have been drafted.

Alexandria is self-contained. It exists in splendid isolation, without depending on, or even acknowledging, other libraries. Serapeum tries to be a good citizen of the Quicklisp era: whenever possible, it avoids duplicating functionality that can be had elsewhere.

Many of the utilities in Serapeum are original ideas; many ideas are borrowed from other languages, or from other Lispers. I try to give credit in the docstrings, but sometimes I have forgotten where I got an idea or a name. I regard missing credits as bugs: please report them.

Serapeum is intended to be portable, but it is principally tested where it is developed, on SBCL and Clozure CL. Patches and bug reports for other Lisps are always welcome, however, including implementation-specific optimizations.

Installation

The preferred way to install Serapeum by using Quicklisp:

(ql:quickload "serapeum")

If you want the very latest version of Serapeum, you can check out the repository into your ~/quicklisp/local-projects directory.

Commentary

One goal of Serapeum is to have excellent documentation. A utility library is a fork of its language; it deserves documentation of the same quality as a language reference. If a utility is not worth documenting, it is not worth having.

The full function reference will be found here. (It is in a separate file in deference to documentation browsers, which often print the README as a preamble to their own function reference).

Most utilities in Serapeum stand alone, but there are some families that deserve separate introduction.

A note about strings

Beginning Lispers often ask about Lisp: “Where are the string utilities?” Since strings in Lisp are a kind of vector, which is in turn a kind of sequence, the right place to look is under the documentation for sequences (and vectors).

This is also true for Serapeum: there are many sequence utilities, and a few vector utilities, that work equally well on strings. But there are also many string-specific utilities.

Dividing sequences

All recent functional programming languages share a family of useful sequence-related functions with terrible names. All of them are called something like “split”, “divide”, or “group”, more or less at random.

For each function, we ensure:

  • It is efficient.
  • It returns like sequences for like (lists for lists, strings for strings, &c.).
  • It accommodates generic sequences (list and vector are not necessarily an exhaustive partition of sequence).
  • It has a distinctive name which does not use any of the weasel words “split,” “divide,” or “group.”

The function that returns runs of like elements in a sequence is called runs:

(runs '(head tail head head tail))
=> '((head) (tail) (head head) (tail))

The function that returns a sequence in batches of a certain maximum size is called batches:

(batches (iota 11) 2)
=> ((0 1) (2 3) (4 5) (6 7) (8 9) (10))

The function which groups the like elements of a sequence is called assort (because it returns a sequence assorted by some property).

(assort (iota 10)
        :key (lambda (n) (mod n 3)))
=> '((0 3 6 9) (1 4 7) (2 5 8))

The function that takes a predicate and a sequence, and returns two sequences – one sequence of the elements for which the function returns true, and one sequence of the elements for which it returns false – is (still) called partition.

(partition #'oddp (iota 10))
=> (1 3 5 7 9), (0 2 4 6 8)

The generalized version of partition, which takes a number of functions and returns the items that satisfy each condition, is called partitions.

(partitions (list #'primep #'evenp) (iota 10))
=> ((2 3 5 7) (0 4 6 8)), (1 9)

Items that do not belong in any partition are returned as a second value.

Serapeum simply re-exports split-sequence, which seems to be firmly rooted under its present name.

Binding values in the function namespace

fbind, fbind*, fbindrec, and fbindrec* bind values in the function namespace.

fbind and fbindrec are like flet and labels, respectively.

(fbind ((fn (lambda ....))) ...)
≡ (flet ((fn ...)) ...)

(fbindrec ((fn (lambda ...))) ...)
≡ (labels ((fn ...)) ...)

fbind* and fbindrec* have no exact parallels: they bind functions in sequence, so that each can be used in the construction (not just the definition, as with fbindrec) of the next.

(fbind* ((flip2 (lambda (fn)
                 (lambda (x y)
                   (funcall fn y x))))
         (xcons (flip2 #'cons)))
  (xcons 2 1))
=> (1 . 2)

These are non-trivial implementations. In many cases, fbind can produce code that is more efficient than using funcall, and even eliminate the overhead of higher-order functions like compose and curry. And fbindrec, which builds on fbind, further implements the optimizing transformation from Waddell et. al., Fixing Letrec. (Note that the macroexpansion of fbind may sometimes appear simplistic, using macroexpand; this is the happy case when we can prove that the function is never used as a value.)

For binding values in the function namespace at the top level, Serapeum provides defalias:

(defalias xcons (flip #'cons))

This is equivalent to (setf (fdefinition ...)), but also gives the function a compile-time definition so compilers don’t complain about its being undefined.

Internal definitions

The local form lets you use top-level definition forms to create local bindings. You can use defun instead of labels, defmacro instead of macrolet, def (which is Serapeum’s macro for top-level lexical bindings) instead of let, and so forth.

This has three advantages:

  1. Given a set of variable, function, and macro bindings, you can leave it to the compiler to figure out how to nest them. (This could be because you are porting a function from a language that uses flat bindings, or just because you are writing a very complicated function.)

  2. You can use macro-defining macros (macros that expand into defmacro), as well as macros that expand into defun forms, to create local bindings.

  3. You can (using local* or block-compile) easily switch to block compilation of top-level functions.

Serapeum’s implementation of internal definitions is as complete as it can be while remaining portable. That means full support for variables, functions, and symbol macros, but restricted support for macros.

Example: macros that work locally and globally

For example, memoizing local functions is usually clumsy; given local you can define a single defmemo form that supports both defun and labels.

(defmacro defmemo (name params &body body)
  (with-gensyms (memo-table args result result?)
    `(let ((,memo-table (make-hash-table :test 'equal)))
       (defun ,name (&rest ,args)
         (multiple-value-bind (,result ,result?)
             (gethash ,args ,memo-table)
           (if ,result?
               ,result
               (setf (gethash ,args ,memo-table)
                     (apply (lambda ,params
                              ,@body)
                              ,args))))))))

At the top level, this expands into an example of “let over defun” (gensyms elided for readability):

;; This source form
(defmemo fibonacci (n)
    (if (<= n 1)
        1
        (+ (fibonacci (- n 1))
           (fibonacci (- n 2)))))
           
;; Expands into...
(let ((memo-table (make-hash-table :test 'equal)))
  (defun fibonacci (&rest args)
    (multiple-value-bind (result result?)
        (gethash args memo-table)
      (if result? result
          (setf (gethash args memo-table)
                (apply (lambda (n)
                         (if (<= n 1)
                             1
                             (+ (fibonacci (- n 1))
                                (fibonacci (- n 2)))))
                       args))))))

But within a local form, it expands differently. This nearly identical source form:

(local
  (defmemo fibonacci (n)
    (if (<= n 1)
        1
        (+ (fibonacci (- n 1))
           (fibonacci (- n 2)))))

  (fibonacci 100))

Expands into this very different code (simplified for readability):

(let (fn)
  (labels ((fibonacci (&rest args)
             (apply fn args)))
    (let ((memo-table (make-hash-table :test 'equal)))
      (setf fn
            (named-lambda fibonacci (&rest args)
              (multiple-value-bind (result result?)
                  (gethash args memo-table)
                (if result? result
                    (setf (gethash args memo-table)
                          (apply
                           (lambda (n)
                             (if (<= n 1) 1
                                 (+ (fibonacci (- n 1))
                                    (fibonacci (- n 2)))))
                           args))))))
      
      (fibonacci 100))))

Example: block compiling

The macro local* is almost the same as local, except that it leaves the last form in the body intact. This is useful for obtaining block compilation in Lisps that don’t have a syntax for it.

During development, you define functions at the top level inside a progn.

 (progn
   (defun aux-fn-1 ...)
   (defun aux-fn-2 ...)
   (defun entry-point ...))

Then, when you decide you want block compilation, simply switch the progn to a local*:

 (local*
   (defun aux-fn-1 ...)
   (defun aux-fn-2 ...)
   (defun entry-point ...))

Which expands into something like:

(labels ((aux-fn-2 ...)
         (aux-fn-1 ...))
  (defun entry-point ...))

This has the slight disadvantage that calls to the entry points, including self calls, will still be compiled as global calls. If you want calls to the entry points to be compiled as local calls, you can use the block-compile macro instead.

Using block-compile, you can write:

(block-compile (:entry-points (entry-point))
  (defun aux-fn-1 ...)
  (defun aux-fn-2 ...)
  (defun entry-point ...))

And have it expand into something like:

(labels ((aux-fn-2 ...)
     (aux-fn-1 ...)
     (entry-point ...))
  (defalias entry-point #'entry-point))

Compile-time exhaustiveness checking

etypecase-of is just like etypecase, except that it takes an additional argument – the type to be matched against – and warns, at compile time, if the clauses in its body are not an exhaustive partition of that type.

ecase-of is a succint variant of etypecase with the same syntax as ecase.

typecase-of and case-of are etypecase-of and ecase-of, respectively, except that they expect, and enforce, the presence of an otherwise clause.

There are also continuable versions of these macros – ctypecase-of and ccase-of.

Example: enums

We may call a type defined using member an enumeration. Take an enumeration like this:

(deftype switch-state ()
  '(member :on :off :stuck :broken))

Now we can use ecase-of to take all the states of the switch into account.

(defun flick (switch)
  (ecase-of switch-state (state switch)
    (:on (switch-off switch))
    (:off (switch-on switch))))
=> Warning

(defun flick (switch)
  (ecase-of switch-state (state switch)
    (:on (switch-off switch))
    (:off (switch-on switch))
    ((:stuck :broken) (error "Sorry, can't flick ~a" switch))))
=> No warning

Even more usefully, we don’t have to worry about bugs caused by misspellings:

(defun flick (switch)
  (ecase-of switch-state (state switch)
    (:on (switch-off switch))
    (:offf (switch-on switch))          ;Gotcha!
    ((:stuck :broken) (error "Sorry, can't flick ~a" switch))))
=> Warning

Example: union types

(defun negative-integer? (n)
  (etypecase-of t n
    ((not integer) nil)
    ((integer * -1) t)
    ((integer 1 *) nil)))
=> Warning

(defun negative-integer? (n)
  (etypecase-of t n
    ((not integer) nil)
    ((integer * -1) t)
    ((integer 1 *) nil)
    ((integer 0) nil)))
=> No warning

This article has more about exhaustiveness checking in Serapeum.

CLOS

Serapeum includes some utilities for CLOS. These utilities do nothing earthshaking, but since the function reference does not include them, they should be documented somewhere.

Method combination: standard with context

Serapeum exports a method combination, serapeum:standard/context. You may recognize it as the wrapping-standard method combination due to Tim Bradshaw.

Generic functions defined with standard/context behave the same as ordinary generic functions, except that they allow an extra qualifier, :context. This extra qualifier works almost like :around, except instead of being run in most-specific-first order, like methods defined with :around, methods defined with :context are run in most-specific-last order. Furthermore, :context methods take priority over any other methods, including :around methods.

The big idea is that a class can use :context methods to make sure that any methods defined by subclasses – even :around methods – run in a certain dynamic context.

Metaclass: topmost-object-class

In most cases, when I write a metaclass, I want all of the classes defined using that metaclass to inherit from a specific class. Injecting a topmost class is not difficult to do, but it involves a certain amount of boilerplate.

To eliminate that boilerplate, Serapeum exports a metaclass, topmost-object-class, to use as a base class for your metaclasses. When you define a metaclass, all you have to do to ensure that classes defined using your metaclass inherit from a specific class is to supply the name of the class to inherit from in the definition of the metaclass. This is much better demonstrated than explained:

;;; The class to inherit from.
(defclass my-topmost-object ()
  ())

;;; The metaclass.
(defclass my-metaclass (serapeum:topmost-object-class)
  ()
  (:default-initargs
   :topmost-class 'my-topmost-object))

(defclass my-class ()
  ()
  (:metaclass my-metaclass))

(typep (make-instance 'my-class) 'my-topmost-object) => t

Note that, since the topmost object is usually a standard class, there is a validate-superclass method which allows an instance of topmost-object-class to inherit from a standard class.

Contributions

The contrib/ directory holds large contributions to Serapeum (ones that add a lot of new exports).

Hooks

The package :serapeum/contrib/hooks holds an enhanced implementation of hooks (extension points) contributed by the maintainers of the Nyxt web browser. This is fully compatible with the existing Serapeum functions for hooks (add-hook, run-hook, etc.).

NB This hook implementation is deprecated; consider nhooks instead.

Function reference

The complete reference is in a separate file.

(Note that the reference is generated from docstrings, and should not be edited by hand.)

serapeum's People

Contributors

aartaka avatar actions-user avatar arademaker avatar astrangeguy avatar bo-tato avatar eudoxia0 avatar fiddlerwoaroof avatar goose121 avatar gos-k avatar joelreymont avatar kchanqvq avatar kilianmh avatar lukego avatar mpsota avatar paulapatience avatar pfdietz avatar phmarek avatar phoe avatar pouar avatar puercopop avatar ruricolist avatar schw1804 avatar sirherrbatka avatar svetlyak40wt avatar thelostlambda avatar tmccombs avatar vindarel 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  avatar  avatar  avatar

serapeum's Issues

ignoring made redundant by ignore-some-conditions

Alexandria's ignore-some-conditions is a superset of Serapeum's ignoring, where ignore-some-conditions can ignore several conditions.

I seem to remember reading about Serapeum's stance on API changes, but I cannot remember exactly where, or what the stance was (I believe it viewed them positively). With this in mind, I propose removing ignoring from Serapeum.

Assort seems not working on vector

Hi,

When I try assort on vector like this:

(assort #(1 2 3))

it would signal an error

The value
  #(1)
is not of type
  SIMPLE-VECTOR

in SBCL 1.4.16.

I don't know if it is a bug or I write it wrong.

Best Regards

Compiling on MacOS Mojave with SBCL 1.4.13

Hi, I'm trying to use Serapeum on MacOS with SBCL 1.4.13 and I get the following error:

COMPILE-FILE-ERROR while
compiling #<CL-SOURCE-FILE "serapeum" "level2" "range">
   [Condition of type UIOP/LISP-BUILD:COMPILE-FILE-ERROR]

Restarts:
 0: [RETRY] Retry compiling #<CL-SOURCE-FILE "serapeum" "level2" "range">.
 1: [ACCEPT] Continue, treating compiling #<CL-SOURCE-FILE "serapeum" "level2" "range"> as having been successful.
 2: [RETRY] Retry ASDF operation.
 3: [CLEAR-CONFIGURATION-AND-RETRY] Retry ASDF operation after resetting the configuration.
 4: [RETRY] Retry ASDF operation.
 5: [CLEAR-CONFIGURATION-AND-RETRY] Retry ASDF operation after resetting the configuration.
 --more--

Backtrace:
  0: (UIOP/LISP-BUILD:CHECK-LISP-COMPILE-RESULTS NIL T T "~/asdf-action::format-action/" ((#<ASDF/LISP-ACTION:COMPILE-OP > . #<ASDF/LISP-ACTION:CL-SOURCE-FILE "serapeum" "level2" "range">)))
  1: ((SB-PCL::EMF ASDF/ACTION:PERFORM) #<unused argument> #<unused argument> #<ASDF/LISP-ACTION:COMPILE-OP > #<ASDF/LISP-ACTION:CL-SOURCE-FILE "serapeum" "level2" "range">)
  2: ((LAMBDA NIL :IN ASDF/ACTION:CALL-WHILE-VISITING-ACTION))
  3: ((:METHOD ASDF/ACTION:PERFORM-WITH-RESTARTS :AROUND (T T)) #<ASDF/LISP-ACTION:COMPILE-OP > #<ASDF/LISP-ACTION:CL-SOURCE-FILE "serapeum" "level2" "range">) [fast-method]
  4: ((:METHOD ASDF/PLAN:PERFORM-PLAN (T)) #<ASDF/PLAN:SEQUENTIAL-PLAN {10022CBC83}>) [fast-method]
  5: ((FLET SB-C::WITH-IT :IN SB-C::%WITH-COMPILATION-UNIT))
  6: ((:METHOD ASDF/PLAN:PERFORM-PLAN :AROUND (T)) #<ASDF/PLAN:SEQUENTIAL-PLAN {10022CBC83}>) [fast-method]
  7: ((:METHOD ASDF/OPERATE:OPERATE (ASDF/OPERATION:OPERATION ASDF/COMPONENT:COMPONENT)) #<ASDF/LISP-ACTION:LOAD-OP > #<ASDF/SYSTEM:SYSTEM "socialflight"> :PLAN-CLASS NIL :PLAN-OPTIONS NIL) [fast-method]
  8: ((SB-PCL::EMF ASDF/OPERATE:OPERATE) #<unused argument> #<unused argument> #<ASDF/LISP-ACTION:LOAD-OP > #<ASDF/SYSTEM:SYSTEM "socialflight"> :VERBOSE NIL)
  9: ((LAMBDA NIL :IN ASDF/OPERATE:OPERATE))
 10: ((:METHOD ASDF/OPERATE:OPERATE :AROUND (T T)) #<ASDF/LISP-ACTION:LOAD-OP > #<ASDF/SYSTEM:SYSTEM "socialflight"> :VERBOSE NIL) [fast-method]
 11: ((SB-PCL::EMF ASDF/OPERATE:OPERATE) #<unused argument> #<unused argument> ASDF/LISP-ACTION:LOAD-OP "socialflight" :VERBOSE NIL)
 12: ((LAMBDA NIL :IN ASDF/OPERATE:OPERATE))
 13: ((:METHOD ASDF/OPERATE:OPERATE :AROUND (T T)) ASDF/LISP-ACTION:LOAD-OP "socialflight" :VERBOSE NIL) [fast-method]
 14: (ASDF/SESSION:CALL-WITH-ASDF-SESSION #<CLOSURE (LAMBDA NIL :IN ASDF/OPERATE:OPERATE) {10022C6B9B}> :OVERRIDE T :KEY NIL :OVERRIDE-CACHE T :OVERRIDE-FORCING NIL)
 15: ((LAMBDA NIL :IN ASDF/OPERATE:OPERATE))
 16: (ASDF/SESSION:CALL-WITH-ASDF-SESSION #<CLOSURE (LAMBDA NIL :IN ASDF/OPERATE:OPERATE) {10022B50CB}> :OVERRIDE NIL :KEY NIL :OVERRIDE-CACHE NIL :OVERRIDE-FORCING NIL)
 17: ((:METHOD ASDF/OPERATE:OPERATE :AROUND (T T)) ASDF/LISP-ACTION:LOAD-OP "socialflight" :VERBOSE NIL) [fast-method]
 18: (ASDF/OPERATE:LOAD-SYSTEM "socialflight" :VERBOSE NIL)
 19: (QUICKLISP-CLIENT::CALL-WITH-MACROEXPAND-PROGRESS #<CLOSURE (LAMBDA NIL :IN QUICKLISP-CLIENT::APPLY-LOAD-STRATEGY) {10022B32EB}>)
 --more--
;   (SERAPEUM/DISPATCH-CASE::DISPATCH-CASE/NOBINDINGS ((#:ARG0 SERAPEUM::REAL*)
;                                                      (#:ARG1 SERAPEUM::REAL*)
;                                                      (#:ARG2 SERAPEUM::REAL*))
;     ((ALEXANDRIA.0.DEV:ARRAY-INDEX ALEXANDRIA.0.DEV:ARRAY-INDEX
;       ALEXANDRIA.0.DEV:NON-NEGATIVE-INTEGER)
;      (GO #:TAG2))
;     ((ALEXANDRIA.0.DEV:NON-NEGATIVE-INTEGER
;       ALEXANDRIA.0.DEV:NON-NEGATIVE-INTEGER
;       ALEXANDRIA.0.DEV:NON-NEGATIVE-INTEGER)
;      (GO #:TAG3))
;     ((INTEGER INTEGER INTEGER) (GO #:TAG4))
;     ((RATIO RATIONAL RATIONAL) (GO #:TAG5))
;     ((RATIONAL RATIO RATIONAL) (GO #:TAG6))
;     ((RATIONAL RATIONAL RATIO) (GO #:TAG7))
;     ((SINGLE-FLOAT SINGLE-FLOAT SINGLE-FLOAT) (GO #:TAG8))
;     ((DOUBLE-FLOAT DOUBLE-FLOAT DOUBLE-FLOAT) (GO #:TAG9))
;     ((SHORT-FLOAT SHORT-FLOAT SHORT-FLOAT) (GO #:TAG10))
;     ((LONG-FLOAT LONG-FLOAT LONG-FLOAT) (GO #:TAG11))
;     ...)
; 
; caught ERROR:
;   during macroexpansion of
;   (SERAPEUM/DISPATCH-CASE::DISPATCH-CASE/NOBINDINGS (# # #)
;     (# #)
;     ...).
;   Use *BREAK-ON-SIGNALS* to intercept.
;   
;    The function SERAPEUM::KEY is undefined.

any help would be greatly appreciated, thanks!

As an aside, I've already tried:

  1. upgrading to the latest Quicklisp official dist
  2. clearing my fasl cache

Alternative to read-line

It would be nice to have an alternative to read-line, along the lines of read-line-into.

If it is too clumsy to be practical to be used directly it could still be wrapped into a nice Iterate driver.

def* macros with export

I like to export symbols at definition site instead of in a separate defpackage declaration: it reduces maintenance and risks of typos / forgotten renames and removals.

Some prefer to have all exported symbols put into one place because this gives the package users a simple overview of the symbols they can use.
I'd argue that:

  • (SLIME) completion does it too. It's easy to do it programmatically with

    (declaim (ftype (function ((or symbol package))) exported-symbols))
    (defun exported-symbols (package)
      "List exported symbols of PACKAGE."
      (let ((package (if (packagep package)
                         package
                         (find-package package)))
            (symbols))
        (do-external-symbols (s package symbols)
          (when (eq (symbol-package s) package)
            (push s symbols)))
        symbols))
  • In case of typos / out-of-sync issues in the defpackage export list, the
    resulting error can be confusing to the user.

The problem is that (export 'sym) is a function and is not expanded at compile time.
Unless wrapped withing a (eval-when ...) that is, but then a simple export
becomes excessively verbose:

(eval-when (:compile-toplevel :load-toplevel :execute)
  (export 'foo))
(defun foo () ...)

Beside the repetition of foo does not reduce the risk for typos.

I propose a bunch of macros:

  • defun-export
  • defvar-export
  • defparameter-export
  • defconstant-export
  • defclass-export
  • defstruct-export
  • defmacro-export
  • defgeneric-export
  • defmethod-export

Those would expand to the above eval-when and the regular "non-export" definition.

Would this be a good fit for this library? If not, any other suggestion then?

More alist access macros.

Hi,
I've written some macros to make alist access nicer for nested alists.
They sure need polish which I'd add if you would be interested in adding them to serapeum.

Cheers.

Two special cases in CASE-USING macro never apply

It you trace EXTRACT-FUNCTION-NAME and then evaluate a CASE-USING form with #'STRING= or #'EQL, you will find EXTRACT-FUNCTION-NAME is applied to some gensymed variable, not to the value of PRED. So, those two branches of the CASE form in the macro function's body never apply.

"There is no function named DECLARE" error during strings.lisp compilation

Sometimes this error occure when I trying to load serapeum under SBCL:

; file: /Users/art/projects/work/cl-dbass-client/quicklisp/dists/quicklisp/software/serapeum-20180711-git/strings.lisp
; in: DEFUN COLLAPSE-WHITESPACE
;     (DECLARE (INLINE POSITION SERAPEUM:WHITESPACEP))
;
; caught ERROR:
;   There is no function named DECLARE.  References to DECLARE in some contexts
;   (like starts of blocks) are unevaluated expressions, but here the expression is
;   being evaluated, which invokes undefined behaviour.
Unhandled UIOP/LISP-BUILD:COMPILE-FILE-ERROR in thread #<SB-THREAD:THREAD "main thread" RUNNING
                                                          {10005505B3}>:
  COMPILE-FILE-ERROR while
  compiling #<CL-SOURCE-FILE "serapeum" "level1" "strings">

Compilation Issue

Hello, trying to compile master, doesn't work:

~ $ sbcl
This is SBCL 2.0.1, an implementation of ANSI Common Lisp.
More information about SBCL is available at <http://www.sbcl.org/>.

SBCL is free software, provided as is, with absolutely no warranty.
It is mostly in the public domain; some portions are provided under
BSD-style licenses.  See the CREDITS and COPYING files in the
distribution for more information.
To load "cffi":
  Load 1 ASDF system:
    cffi
; Loading "cffi"
........
* (ql:quickload :serapeum)
To load "serapeum":
  Load 1 ASDF system:
    serapeum
; Loading "serapeum"
.
Switching to the BALLAND2006 optimizer
.........INFO: Control stack guard page unprotected
Control stack guard page temporarily disabled: proceed with caution

debugger invoked on a SB-KERNEL::CONTROL-STACK-EXHAUSTED in thread
#<THREAD "main thread" RUNNING {1000560083}>:
  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.

Type HELP for debugger help, or (SB-EXT:EXIT) to exit from SBCL.

restarts (invokable by number or by possibly-abbreviated name):
  0: [RETRY                        ] Retry
                                     compiling #<CL-SOURCE-FILE "serapeum" "level2" "range">.
  1: [ACCEPT                       ] Continue, treating
                                     compiling #<CL-SOURCE-FILE "serapeum" "level2" "range">
                                     as having been successful.
  2:                                 Retry ASDF operation.
  3: [CLEAR-CONFIGURATION-AND-RETRY] Retry ASDF operation after resetting the
                                     configuration.
  4:                                 Retry ASDF operation.
  5:                                 Retry ASDF operation after resetting the
                                     configuration.
  6: [ABORT                        ] Give up on "serapeum"
  7:                                 Exit debugger, returning to top level.

(SB-KERNEL::CONTROL-STACK-EXHAUSTED-ERROR)
0] 

any ideas? thanks cc: @Ambrevar

scan seems to be wrong

first, of, the order argument in the callback is REVERSE from the standard reduce. Secondly key callback is not applied to the next value, just to the previous, what's up with that?

serapeum/vector= Can't compile current version

I cloned the current commit into my system.

It can't compile because of an error on a format directive:

[package serapeum/vector=]..

; file: c:/portacle/projects/serapeum/vector=.lisp
; in: DEFCONSTRUCTOR BOUNDS
;     (SERAPEUM:DEFCONSTRUCTOR SERAPEUM/VECTOR=::BOUNDS
;       (SERAPEUM/VECTOR=::START1 ALEXANDRIA.0.DEV:ARRAY-INDEX)
;       (SERAPEUM/VECTOR=::END1 ALEXANDRIA.0.DEV:ARRAY-LENGTH)
;       (SERAPEUM/VECTOR=::START2 ALEXANDRIA.0.DEV:ARRAY-INDEX)
;       (SERAPEUM/VECTOR=::END2 ALEXANDRIA.0.DEV:ARRAY-LENGTH))
; 
; caught ERROR:
;   (during macroexpansion of (DEFCONSTRUCTOR BOUNDS
;     ...))
;   error in FORMAT: unknown format directive (character: Return)
;     Copy an instance of ~:@(~a~), optionally ~

;   overriding some or all of its slots.
;                                               ^
;   while processing indirect format string:
;     ~?
;      ^
.....; 
     ; compilation unit aborted
     ;   caught 2 fatal ERROR conditions
     ;   caught 1 ERROR condition

Thus, i can't compile the current version for spinneret, another fine, quality product from Ruricolist.

ECL seems to complain about MATCHED-TYPES being bound with let

[package serapeum/dispatch-case].
;;; Error:
;;;   in file dispatch-case.lisp, position 959
;;;   at (FSET 'WITH-MATCHED-TYPE ...)
;;;   * The constant MATCHED-TYPES is being bound.
Condition of type: COMPILE-FILE-ERROR
COMPILE-FILE-ERROR while compiling #<cl-source-file "serapeum" "level2" "dispatch-case">

The following patch seems to pacify it

diff --git a/dispatch-case.lisp b/dispatch-case.lisp
index d739f01..93560ae 100644
--- a/dispatch-case.lisp
+++ b/dispatch-case.lisp
@@ -22,16 +22,16 @@
 (define-symbol-macro matched-types ())
 
 (defmacro with-matched-type (type &body body &environment env)
-  (let ((matched-types (macroexpand-1 'matched-types env)))
-    `(symbol-macrolet ((matched-types ,(cons type matched-types)))
+  (let ((%matched-types (macroexpand-1 'matched-types env)))
+    `(symbol-macrolet ((matched-types ,(cons type %matched-types)))
        ,@body)))
 
 (defmacro dispatch-case-error (&key type datum &environment env)
-  (let ((matched-types (macroexpand-1 'matched-types env)))
+  (let ((%matched-types (macroexpand-1 'matched-types env)))
     `(error 'dispatch-case-error
             :expected-type ,type
             :datum ,datum
-            :matched-types ',(butlast matched-types))))
+            :matched-types ',(butlast %matched-types))))
 
 (defun clause-leading-type (clause)
   (caar clause))

Guix package compilation error

; compiling (DEFUN FLOAT-PRECISION-CONTAGION ...)
; file: /gnu/store/81mwbkhih0v063r2cbs2b9kp70dk4l39-sbcl-serapeum-0.0.0-0.9cc0f9c/share/common-lisp/sbcl-source/serapeum/numbers.lisp
; in: DEFUN FLOAT-PRECISION-CONTAGION
;     (SERAPEUM:OP
;       (+ SERAPEUM::_ SERAPEUM::ZERO))
; 
; caught ERROR:
;   during macroexpansion of
;   (OP
;     (+ _ ZERO)).
;   Use *BREAK-ON-SIGNALS* to intercept.
;   
;    The function SERAPEUM/OP::EXTRACT-OP-ENV is undefined.

;     (MAPCAR
;      (SERAPEUM:OP
;        (+ SERAPEUM::_ SERAPEUM::ZERO))
;      SERAPEUM::NS)
; --> LET 
; ==>
;   (SB-KERNEL:%COERCE-CALLABLE-TO-FUN
;    (SERAPEUM:OP
;      (+ SERAPEUM::_ SERAPEUM::ZERO)))
; 
; note: The first argument never returns a value.

;     (SERAPEUM:OP
;       (* SERAPEUM::_ 0))
; 
; caught ERROR:
[...]

Any idea where that could come from?

Compiler macro for `#'vect` causes problems for vectors of lists

(vect (list 'foo)) breaks in compiled code on SBCL because the compiler-macro declares (list 'foo)dynamic-extent at the same time as it declares the temporary list for passing to make-array dynamic-extent.

This is a very particular edge case, and one that can be easily solved by users without any change to vect, but it is very surprising when you're not expecting it. At the very least, a note in the docs would be appreciated.

As a side note, this is reproducible at the repl by wrapping the example above in a lambda, as in ((lambda () (vect (list 'foo)))). The result is a vector containing junk data.

Compiler macro for MVFOLDR produces error.

If I do

(defun foo ()
  (serapeum:mvfoldr (lambda (val min max)
                      (values (min min val) (max max val)))
                    (loop for i below 100 collect i)
                    0
                    0))

(bar)

This results in the following error.

Form:
  (SERAPEUM::DO-SUBSEQ (#1=#:ITEM2
                      (LOOP FOR I BELOW 100
                            COLLECT I)
                      :FROM-END T)
  (SETF (VALUES . #2=(#:G0 #:G1)) (FUNCALL #:FN3 #1# . #2#)))
Compile-time error:
  during macroexpansion of
(SERAPEUM::DO-SUBSEQ (#:ITEM2 # :FROM-END ...)
  (SETF #)).
Use *BREAK-ON-SIGNALS* to intercept.

 error while parsing arguments to DO-SUBSEQ DEFMACRO:
   odd number of elements in keyword/value list: (T)

The compiler macro calls EXPAND-MVFOLD.

(defun expand-mvfold (fn seq seeds &optional from-end)
    (cond ((null seeds)
           `(reduce ,fn ,seq :from-end ,from-end))
          ((null (cdr seeds))
           `(reduce ,fn ,seq
                    :from-end ,from-end
                    :initial-value ,(car seeds)))
          (t (let ((tmps (make-gensym-list (length seeds))))
               (with-gensyms (item)
                 (rebinding-functions (fn)
                   `(let ,(mapcar #'list tmps seeds)
                      ,(if from-end
                           `(do-subseq (,item ,seq :from-end t)
                              (setf (values ,@tmps)
                                    (funcall ,fn ,item ,@tmps)))
                           `(do-each (,item ,seq)
                              (setf (values ,@tmps)
                                    (funcall ,fn ,@tmps ,item))))
                      (values ,@tmps))))))))

If EXPAND-MVFOLD is called with :from-end t, which is the case for MVFOLDR, the do-subseq form is missing an optional return parameter and therefore consumes :from-end which causes the error.

This seems to be easily fixed by e.g. adding (values ,@tmps) to both do-subseq forms and omitting it at the end of the let.

(defun expand-mvfold (fn seq seeds &optional from-end)
    (cond ((null seeds)
           `(reduce ,fn ,seq :from-end ,from-end))
          ((null (cdr seeds))
           `(reduce ,fn ,seq
                    :from-end ,from-end
                    :initial-value ,(car seeds)))
          (t (let ((tmps (make-gensym-list (length seeds))))
               (with-gensyms (item)
                 (rebinding-functions (fn)
                   `(let ,(mapcar #'list tmps seeds)
                      ,(if from-end
                           `(do-subseq (,item ,seq (values ,@tmps) :from-end t)
                              (setf (values ,@tmps)
                                    (funcall ,fn ,item ,@tmps)))
                           `(do-each (,item ,seq (values ,@tmps))
                              (setf (values ,@tmps)
                                    (funcall ,fn ,@tmps ,item)))))))))))

Allow using a different name for collecting

I would like a way to specify a different name for the collect function in the collecting macro. This would be useful in scenarios where you have nested collecting macros, or want to call the collect method inside an iterate:iter form.

Lispworks missing characters.

Missing character names on lispworks:

 COMPILE-FILE-ERROR while compiling #<ASDF/LISP-ACTION:CL-SOURCE-FILE "serapeum" "strings">
  1 (continue) Retry compiling #<ASDF/LISP-ACTION:CL-SOURCE-FILE "serapeum" "strings">.
  2 Continue, treating compiling #<ASDF/LISP-ACTION:CL-SOURCE-FILE "serapeum" "strings"> as having been successful.
  3 Retry ASDF operation.
  4 Retry ASDF operation after resetting the configuration.
  5 (abort) Give up on "cl-testing"
  6 Return to level 1.
  7 Return to debug level 1.
  8 Return to level 0.
  9 Return to top loop level 0.

Type :b for backtrace or :c <option number> to proceed.
Type :bug-form "<subject>" for a bug report template or :? for other options.

MY-PACKAGE 53 : 2 > :c 1

**++++ Error between functions:
  Wrong character name: NO-BREAK_SPACE.

**++++ Error between functions:
  The variable NO-BREAK-SPACE is unbound.

**++++ Error between functions:
  The variable WHITESPACE is unbound.

Use queue like a sequence?

During working with queue, I found it's unconvenient for there is no iteration interface for queue.

In many times, I have to follow the flow:

myqueue: 
=> (qlist myqueue) 
=> operating on sequence... 
=> (apply 'queue mysequnce)

Required API:
qiter, qinto corresponds to map on first level of queue.
qwalk, qmap corresponds to map on the whole queue tree.
qlist-1, qlist corresponds to old qlist and qlist-1 for all level.

Or It's better to impl sequnce method for queue, for example http://research.gold.ac.uk/2344/1/sequences-20070301.pdf

Equivalent of `uniq`

It would be nice to have a utility that does what uniq does on the command line -- eliminate adjacent repetitions. Obviously it would better than remove-duplicates (or nub) for data that is already sorted. But: uniq is a terrible name.

Candidates:

  • squeeze-repeats
  • remove-repeats (and delete-repeats)
  • first-runs (since this is equivalent to mapping first-elt over the result of runs)
  • run-heads

Add a compile-bundle-op test

A similar error occurred in the past when I tried to package serapeum for Guix.
The fix was in the .asd.

; file: /gnu/store/spzi46n7wgmd3k64m7q6nrbd43qa0z0c-sbcl-serapeum-0.0.0-1.6aba6d5/share/common-lisp/sbcl-source/serapeum/sequences.lisp
; in: DEFSUBST SINGLE
;     (SERAPEUM:DEFSUBST SERAPEUM:SINGLE
;         (SERAPEUM::SEQ)
;       "Is SEQ a sequence of one element?"
;       (SERAPEUM::SEQ-DISPATCH SERAPEUM::SEQ
;         (AND SERAPEUM::SEQ (ENDP (CDR SERAPEUM::SEQ)))
;         (= (LENGTH SERAPEUM::SEQ) 1)))
; --> PROGN DECLAIM EVAL-WHEN 
; ==>
;   (SB-C::%PROCLAIM '(INLINE SERAPEUM:SINGLE) (SB-C:SOURCE-LOCATION))
; 
; caught STYLE-WARNING:
;   Proclaiming SERAPEUM:SINGLE to be INLINE, but 4 calls to it were previously
;   compiled. A declaration of NOTINLINE at the call sites will eliminate this
;   warning, as will proclaiming and defining the function before its first
;   potential use.

; compiling (DEFTYPE SINGLE ...)
; compiling (DEFUN ONLY-ELT ...)
; compiling (DEFUN ROTATION ...)
; compiling (DEFUN PARTITION ...)
; compiling (DEFUN PARTITIONS ...)
; compiling (DEFCONSTRUCTOR AGROUP ...)
; file: /gnu/store/spzi46n7wgmd3k64m7q6nrbd43qa0z0c-sbcl-serapeum-0.0.0-1.6aba6d5/share/common-lisp/sbcl-source/serapeum/sequences.lisp
; in: DEFCONSTRUCTOR AGROUP
;     (SERAPEUM:DEFCONSTRUCTOR SERAPEUM::AGROUP
;       "Auxiliary data structure for `assort'. A pair of an exemplar (to
;   compare against) and a bucket of matching items. Note that while the
;   agroup is immutable, the bucket itself is mutable."
;       (SERAPEUM::EXEMPLAR T)
;       (SERAPEUM::BUCKET T))
; --> PROGN 
; ==>
;   (SERAPEUM:DEFSTRUCT-READ-ONLY (SERAPEUM::AGROUP
;                                  (:CONSTRUCTOR SERAPEUM::AGROUP
;                                   (SERAPEUM::EXEMPLAR SERAPEUM::BUCKET))
;                                  (:CONC-NAME SERAPEUM::AGROUP-)
;                                  (:PREDICATE NIL)
;                                  (:PRINT-FUNCTION
;                                   (LAMBDA
;                                       (SERAPEUM::OBJECT STREAM SERAPEUM::DEPTH)
;                                     (DECLARE #)
;                                     (LET #
;                                       #
;                                       #))))
;     "Auxiliary data structure for `assort'. A pair of an exemplar (to
; compare against) and a bucket of matching items. Note that while the
; agroup is immutable, the bucket itself is mutable."
;     (SERAPEUM::EXEMPLAR :TYPE T)
;     (SERAPEUM::BUCKET :TYPE T))
; 
; caught ERROR:
;   (during macroexpansion of (DEFSTRUCT-READ-ONLY (AGROUP # ...)
;     ...))
;   The function SERAPEUM:CAR-SAFE is undefined.

What do you think of adding a compile-bundle-op test? :)

Array Length Miscalculation for RANGE & Buffer Overflow

Sorry if this is a bit terse, I'm pressed for time and wanted to get this written before I forgot. If I'm mistaken about something just let me know.

Expected:
(range -2 5 2) => #(-2 0 2 4)
Actual:
(range -2 5 2) => #(-2 0 2)

The length is calcuated by int-range-shape, on line 127 of range.lisp in a let binding:

(len (abs (truncate (- high low) step)))

If (mod (- high low) step) is not zero we end up one short in our calculation of the range's number of elements.

While I haven't exhaustively tested it, the following snippet seems to correctly calculate the length:

(multiple-value-bind (quotient remainder)
    (truncate (- high low) step)
  (if (zerop remainder)
      (abs quotient)
      (1+ (abs quotient))))

Related to this, fill-int-range! iterates over the proper length of the array, resulting in an array bounds condition on SBCL 2.0.1 if I recompile the function without the #.no-bounds-checks declaration. I think it without bounds checks it just overflows the array.

Human size

I found the need to print (file) sizes in a human readable manner, using the SI or IEC units.

Emacs has such a function, but it has some quirks, so I rewrote it:

;; This is mostly inspired by Emacs 26.2.
(defun file-size-human-readable (file-size &optional flavor)
  "Produce a string showing FILE-SIZE in human-readable form.

Optional second argument FLAVOR controls the units and the display format:

 If FLAVOR is nil or omitted, each kilobyte is 1024 bytes and the produced
    suffixes are \"k\", \"M\", \"G\", \"T\", etc.
 If FLAVOR is `si', each kilobyte is 1000 bytes and the produced suffixes
    are \"k\", \"M\", \"G\", \"T\", etc.
 If FLAVOR is `iec', each kilobyte is 1024 bytes and the produced suffixes
    are \"KiB\", \"MiB\", \"GiB\", \"TiB\", etc."
  (let ((power (if (or (null flavor) (eq flavor 'iec))
                   1024.0
                   1000.0))
        (post-fixes
          ;; none, kilo, mega, giga, tera, peta, exa, zetta, yotta
          (list "" "k" "M" "G" "T" "P" "E" "Z" "Y"))
        (format-string "~d~a~a"))
    (loop while (and (>= file-size power) (rest post-fixes))
          do (setf file-size (/ file-size power)
                   post-fixes (rest post-fixes)))
    (if (> (abs (- file-size (round file-size))) 0.05)
        (setf format-string "~,1f~a~a")
        (setf file-size (round file-size)))
    (format nil format-string
            file-size
            (if (and (eq flavor 'iec) (string= (first post-fixes) "k"))
                "K"
                (first post-fixes))
            (cond
              ((and (eq flavor 'iec)
                    (string= (first post-fixes) ""))
               "B")
              ((eq flavor 'iec) "iB")
              (t "")))))

Would this be a good candidate for Serapeum? If not, another library to suggest?

Basic summary statistics

The statistical functions in Alexandria -- in particular mean, variance, and standard-deviation -- are attractive nuisances: authoritatively named functions in the most popular utility library, but written with no concern for numerical stability.

We are committed to not conflicting with Alexandria, but it would be a public service to export numerically stable alternatives to these functions.

Really need `back` method for `queue`!

Some times, maybe more frequently, you really need get the tail element of the queue.
Though, I can write my own version as a workaround:

(defun back (serapeum-queue)
  (alexandria:last-elt (qlist serapeum-queue)))

Supply a back method for queue from serapeum is the better way.
since there is already a front method:

(first (qlist queue)))

failed compilation of KEY-TEST on ECL

Hello,

I ran into this problem with ecl 16.1.3 and the 2018-04-30 dist of quicklisp while loading
serapeum:

Linux violet > ecl
;;; Loading "/home/psilord/quicklisp/setup.lisp"
;;; Loading #P"/usr/local/lib/ecl-16.1.3/asdf.fas"
ECL (Embeddable Common-Lisp) 16.1.3 (git:UNKNOWN)
Copyright (C) 1984 Taiichi Yuasa and Masami Hagiya
Copyright (C) 1993 Giuseppe Attardi
Copyright (C) 2000 Juan J. Garcia-Ripoll
Copyright (C) 2016 Daniel Kochmanski
ECL is free software, and you are welcome to redistribute it
under certain conditions; see file 'Copyright' for details.
Type :h for Help.  
Top level in: #<process TOP-LEVEL>.
> (ql:quickload :serapeum)
To load "serapeum":
  Load 1 ASDF system:
    serapeum
; Loading "serapeum"
;;; Warning: Class TOPMOST-OBJECT-CLASS has been forward referenced.
;;;
;;; Compiling /home/psilord/quicklisp/dists/quicklisp/software/serapeum-20180430-git/sequences.lisp.
;;; OPTIMIZE levels: Safety=3, Space=0, Speed=1, Debug=3
;;;
;;; Compiling (DEFSUBST SEQUENCE? ...).
;;; Compiling (DEFUN CANONICALIZE-KEY ...).
;;; Compiling (DEFUN CANONICALIZE-TEST ...).
;;; Compiling (DEFUN KEY-TEST ...).
.
;;; Error:
;;;   in file sequences.lisp, position 1487
;;;   at (DEFUN KEY-TEST ...)
;;;   * The macro form (FBIND KEY (WITH-TEST-FN (TEST) (LAMBDA (X Y) (TEST (KEY X) (KEY Y))))) was not expanded successfully.
;;; Error detected:
;;; Detected access to an invalid or protected memory address.
Condition of type: COMPILE-FILE-ERROR
COMPILE-FILE-ERROR while compiling #<cl-source-file "serapeum" "level1" "sequences">

Available restarts:

1. (RETRY) Retry compiling #<cl-source-file "serapeum" "level1" "sequences">.
2. (ACCEPT) Continue, treating compiling #<cl-source-file "serapeum" "level1" "sequences"> as having been successful.
3. (RETRY) Retry ASDF operation.
4. (CLEAR-CONFIGURATION-AND-RETRY) Retry ASDF operation after resetting the configuration.
5. (ABORT) Give up on "serapeum"
6. (RESTART-TOPLEVEL) Go back to Top-Level REPL.

Broken at SI:BYTECODES. [Evaluation of: (QUICKLISP-CLIENT:QUICKLOAD :SERAPEUM)] In: #<process TOP-LEVEL>.

Thank you!

undefined function SERAPEUM::ITEM error when building with ABCL

When trying to load serapeum with ABCL, I get the following error:

The function SERAPEUM::ITEM is undefined.
   [Condition of type UNDEFINED-FUNCTION]

Restarts:
 0: [CONTINUE] Try again.
 1: [USE-VALUE] Specify a function to call instead.
 2: [RETURN-VALUE] Return one or more values from the call to SERAPEUM::ITEM.
 3: [RETRY] Retry compiling #<ASDF/LISP-ACTION:CL-SOURCE-FILE "serapeum" "level2" "range">.
 4: [ACCEPT] Continue, treating compiling #<ASDF/LISP-ACTION:CL-SOURCE-FILE "serapeum" "level2" "range"> as having been successful.
 5: [RETRY] Retry ASDF operation.
 --more--

Backtrace:
  0: (#<FUNCTION {23FEAB4D}> #<UNDEFINED-FUNCTION {6B2EA6C4}> #<FUNCTION {23FEAB4D}>)
  1: (APPLY #<FUNCTION {23FEAB4D}> (#<UNDEFINED-FUNCTION {6B2EA6C4}> #<FUNCTION {23FEAB4D}>))
  2: (SYSTEM::RUN-HOOK SYSTEM::*INVOKE-DEBUGGER-HOOK* #<UNDEFINED-FUNCTION {6B2EA6C4}> #<FUNCTION {23FEAB4D}>)
  3: (INVOKE-DEBUGGER #<UNDEFINED-FUNCTION {6B2EA6C4}>)
  4: (ERROR #<UNDEFINED-FUNCTION {6B2EA6C4}>)
  5: (SYSTEM:UNDEFINED-FUNCTION-CALLED SERAPEUM::ITEM ((ALEXANDRIA.0.DEV:ARRAY-INDEX ALEXANDRIA.0.DEV:NON-NEGATIVE-INTEGER INTEGER RATIO RATIONAL SINGLE-FLOAT ...)))
  6: (SERAPEUM::ITEM (ALEXANDRIA.0.DEV:ARRAY-INDEX ALEXANDRIA.0.DEV:NON-NEGATIVE-INTEGER INTEGER RATIO RATIONAL SINGLE-FLOAT ...))
  7: (SERAPEUM:ORDERING (ALEXANDRIA.0.DEV:ARRAY-INDEX ALEXANDRIA.0.DEV:NON-NEGATIVE-INTEGER INTEGER RATIO RATIONAL SINGLE-FLOAT ...) :TEST #<EQL {3DF83170}> :UNORDERED-TO-END NIL ...)
  8: (SERAPEUM:TOPOSORT ((ALEXANDRIA.0.DEV:ARRAY-INDEX ALEXANDRIA.0.DEV:NON-NEGATIVE-INTEGER) (ALEXANDRIA.0.DEV:ARRAY-INDEX INTEGER) (ALEXANDRIA.0.DEV:ARRAY-INDEX RATIONAL) (ALEXANDRIA.0.DEV:NON-NEGATIVE-I..
  9: (SERAPEUM/DISPATCH-CASE::SORT-CLAUSES (((ALEXANDRIA.0.DEV:ARRAY-INDEX ALEXANDRIA.0.DEV:ARRAY-INDEX ALEXANDRIA.0.DEV:NON-NEGATIVE-INTEGER) (GO #:TAG149729)) ((ALEXANDRIA.0.DEV:NON-NEGATIVE-INTEGER ALEX..
 10: ((MACRO-FUNCTION SERAPEUM/DISPATCH-CASE::DISPATCH-CASE/NOBINDINGS) (SERAPEUM/DISPATCH-CASE::DISPATCH-CASE/NOBINDINGS ((#:ARG0 SERAPEUM::REAL*) (#:ARG1 SERAPEUM::REAL*) (#:ARG2 SERAPEUM::REAL*)) ((ALEX..
 11: (MACROEXPAND-1 (SERAPEUM/DISPATCH-CASE::DISPATCH-CASE/NOBINDINGS ((#:ARG0 SERAPEUM::REAL*) (#:ARG1 SERAPEUM::REAL*) (#:ARG2 SERAPEUM::REAL*)) ((ALEXANDRIA.0.DEV:ARRAY-INDEX ALEXANDRIA.0.DEV:ARRAY-INDE..
 12: (PRECOMPILER::PRECOMPILE1 (SERAPEUM/DISPATCH-CASE::DISPATCH-CASE/NOBINDINGS ((#:ARG0 SERAPEUM::REAL*) (#:ARG1 SERAPEUM::REAL*) (#:ARG2 SERAPEUM::REAL*)) ((ALEXANDRIA.0.DEV:ARRAY-INDEX ALEXANDRIA.0.DEV..
 13: (PRECOMPILER::PRECOMPILE-TAGBODY (TAGBODY (SERAPEUM/DISPATCH-CASE::DISPATCH-CASE/NOBINDINGS (# # #) (# #) (# #) (# #) (# #) ...) #:TAG149729 (RETURN-FROM #:BLOCK149728 (PROGN #)) #:TAG149730 (RETURN-F..
 14: (PRECOMPILER::PRECOMPILE1 (TAGBODY (SERAPEUM/DISPATCH-CASE::DISPATCH-CASE/NOBINDINGS (# # #) (# #) (# #) (# #) (# #) ...) #:TAG149729 (RETURN-FROM #:BLOCK149728 (PROGN #)) #:TAG149730 (RETURN-FROM #:B..
 15: (PRECOMPILER::PRECOMPILE-BLOCK (BLOCK #:BLOCK149728 (TAGBODY (SERAPEUM/DISPATCH-CASE::DISPATCH-CASE/NOBINDINGS # # # # # ...) #:TAG149729 (RETURN-FROM #:BLOCK149728 #) #:TAG149730 (RETURN-FROM #:BLOCK..
 16: (PRECOMPILER::PRECOMPILE1 (BLOCK #:BLOCK149728 (TAGBODY (SERAPEUM/DISPATCH-CASE::DISPATCH-CASE/NOBINDINGS # # # # # ...) #:TAG149729 (RETURN-FROM #:BLOCK149728 #) #:TAG149730 (RETURN-FROM #:BLOCK14972..
 17: (PRECOMPILER::PRECOMPILE-PROGN (PROGN (BLOCK #:BLOCK149728 (TAGBODY # #:TAG149729 # #:TAG149730 # ...))))
 18: (PRECOMPILER::PRECOMPILE1 (PROGN (BLOCK #:BLOCK149728 (TAGBODY # #:TAG149729 # #:TAG149730 # ...))))
 19: (PRECOMPILER::PRECOMPILE1 (SERAPEUM:WITH-READ-ONLY-VARS (#:ARG0 #:ARG1 #:ARG2) (BLOCK #:BLOCK149728 (TAGBODY # #:TAG149729 # #:TAG149730 # ...))))
 --more--

Enhancing hooks

Serapeum has simple hooks, but while working with Next I figured they might not be enough.

In Next we use
https://github.com/scymtym/architecture.hooks mostly because I didn't know that Serapeum had hooks :p cl-hooks and Serepeum hooks seem to overlap a lot.

We've discussed some of the shortcomings of cl-hooks there:
https://github.com/scymtym/architecture.hooks/issues.
In short:

  • It'd be nice to have a hook type.
  • It'd be nice to have the ability to list all hooks, if possible without a global variable.
  • It'd be nice to be able to customize how hooks execution is composed. For instance, some hooks might return a list of values, others could be executed in reverse order, others could be reduced (the next hook takes as argument the return value of the previous one -- great for chaining filters!).

What's most problematic with hooks and as the Emacs experience has showed us is that they don't play well with lambda functions:

  • Lambdas are effectively blackboxes once added to the hook.
  • Lambdas don't compare, so adding the same lambda twice will stack it instead of being ignored.

We discussed this here: atlas-engineer/nyxt#419.

My solution to this was to implement a "handler" type which would allow the user to add anonymous functions to a hook but with extra data so that the handler can be compared and introspected to some extent.

Thoughts?
Let me know if this is a bit obscure, I can provide more examples.

New defun* macro for type declaration

Common Lisp has a nice (gradual) type system with support for algebraic data types.

However declaring function types can be cumbersome:

(declaim (ftype (function (ARG-TYPES) RETURN-TYPES)) FUNCTION-NAME)
(defun FUNCTION-NAME ...)

Besides the repetition of the function name and the keyword arguments (if any) is prone to typo errors.

It'd be nice to have a defun* macro where we can specify the types inline, e.g.

(defun* foo ((arg1 :string) &key ((arg2 :integer) default-value)) (:integer)
  "docstring"
  ...
)

Thoughts?

This could be done together with #38.

what define-train does and why it is not exported?

Hello, I was checking the content of package for new stuff and noticed interesting macro called define-train. It is not exported (and neither hook or fork is). It is also not documented, yet it looks like something that should be exported. Do I miss something?

executable find and binary path

I like Emacs' executable-find.
Here is a quick hack that works in Common Lisp:

(defun executable-find (command)
  "Search for COMMAND in the PATH and return the absolute file name.
Return nil if COMMAND is not found anywhere."
  (multiple-value-bind (path)
      (ignore-errors
       (uiop:run-program (format nil "command -v ~A" command)
                         :output '(:string :stripped t)))
    path))

Now obviously to implement it properly we would not use the command executable.

In particular, this can be useful to locate the path of the Lisp binary we are running, e.g. with

(executable-path (uiop:argv0))

define-post-modify-hook issue

(defun my-plus (x y)
  (+ x y))

(define-modify-macro my-incf (&optional (delta 1)) my-plus)

(serapeum:define-post-modify-macro my-incf* (&optional (delta 1)) my-plus)

(defclass foo ()
  ((x :accessor x
      :initform 42)))

;;;

CL-USER> (let ((foo (make-instance 'foo)))
           (my-incf (x foo))
           (x foo))
43 (6 bits, #x2B, #o53, #b101011)


CL-USER> (let ((foo (make-instance 'foo)))
           (my-incf* (x foo))
           (x foo))
;; in: LET ((FOO (MAKE-INSTANCE 'FOO)))
;; (MY-INCF* (X FOO))

;; caught ERROR:
;; during macroexpansion of (MY-INCF* (X FOO)). Use *BREAK-ON-SIGNALS* to
;; intercept.

;; The value
;; #:FOO0
;; is not of type
;; LIST

;; compilation unit finished
;; caught 1 ERROR condition

;; However, this works as expected:
CL-USER> (let ((x 42))
           (values (my-incf* x)
                   x))
42 (6 bits, #x2A, #o52, #b101010)
43 (6 bits, #x2B, #o53, #b101011)

Like constantly, but for multiple values

Like constantly in CMUCL.

Easy to implement, but needs a snappy name.

Candidate names:

  • multiple-value-constantly
  • constantly-values
  • mvconstantly
  • constantly*
  • always (cf. Dylan) (but: symbol conflicts with loop)

local's def vs. defvar

The local macro supports defun, etc. but surprisingly it does not support defvar. Instead, the user must use def.

I wonder why that is. Wouldn't that trip the user? Why not supporting defvar for consistency?

How about a "pretty-print-hash-table" ? A proposal.

Hello,

I don't see such a function. It would be useful to have.

What about the following, which I adapted from Rutils, but in this version without pprint-indent which was messing the terminal output (it's fine on Slime):

(defparameter *current-pprint-indentation* 1)

(defun print-hash-table (ht &optional (stream *standard-output*))
  "Pretty print hash-table HT to STREAM."
  ;; We use *current-pprint-indentation* instead of the built-in pprint-indent and friends
  ;; because printing in the terminal prints too many tabs and too many lines in-between elements.
  (let ((*print-pretty* t)
        (i 0))
    (pprint-logical-block (stream nil)
      (format stream "~&")
      (format stream "~vt" *current-pprint-indentation*)
      (princ "(dict " stream)
      (unless (eq (hash-table-test ht) 'equal)
        (princ #\' stream)
        (princ (hash-table-test ht) stream))
      (incf *current-pprint-indentation*)
      (format stream "~vt" *current-pprint-indentation*)
      (block nil
        (maphash (lambda (k v)
                   (format stream "~&")
                   (when (and *print-length* (> (incf i) *print-length*))
                     (princ "..." stream)
                     (return))
                   (when (and k (listp k))
                     (princ #\' stream))
                   (if (typep k 'hash-table)
                       (print-hash-table k stream)
                       (format stream "~vt~s" *current-pprint-indentation* k))
                   (princ " " stream)
                   (when (and v (listp v))
                     (princ #\' stream))
                   (if (typep v 'hash-table)
                       (print-hash-table v stream)
                       (format stream "~s" v)))
                 ht))
      (decf *current-pprint-indentation*)
      (format stream "~vt" *current-pprint-indentation*)
      (format stream "~&")
      (format stream "~vt) " *current-pprint-indentation*)))
  ht)
(dict 'eql :a 1 :c '(3 three) :d (dict :e "e"))

 (dict 'EQL 
  :A 1
  :C '(3 THREE)
  :D 
  (dict  
   :E "e" 
  )  
 ) 
(gethash :c (read-from-string "
 (dict 'EQL 
  :A 1
  :C '(3 THREE)
  :D 
  (dict  
   :E "e" 
  )  
 ) "))
(3 THREE)
T

serapeum doesn't show up in the "utilities" category on quickdocs

20:17 < cgay> phoe: serapeum doesn't show up in the "utilities" category on quickdocs: 
              http://quickdocs.org/search?q=utilities  you can find it by search for serapeum, but you have to know 
              the name first. not sure if you're the author...might be worth fixing.

Can't build with SBCL if declarations are ON

It gets stuck in infinte recursion. The declaration in question is:

(proclaim '(optimize (safety 3) (speed 0) (compilation-speed 0) (debug 3)))

Output:

➜  ~ sbcl                                                                                                               
This is SBCL 1.5.8, an implementation of ANSI Common Lisp.
More information about SBCL is available at <http://www.sbcl.org/>.

SBCL is free software, provided as is, with absolutely no warranty.
It is mostly in the public domain; some portions are provided under
BSD-style licenses.  See the CREDITS and COPYING files in the
distribution for more information.
* (ql:quickload 'serapeum)
To load "serapeum":
  Load 1 ASDF system:
    serapeum
; Loading "serapeum"
.
Switching to the BALLAND2006 optimizer
.................................................
[package serapeum]................................
[package serapeum-user]...........................
..................................................
[package serapeum/op].............................
..................................................
[package serapeum/vector=]........................
[package serapeum/mop]............................
[package serapeum/internal-definitions]...........
[package serapeum/dispatch-case].......INFO: Control stack guard page unprotected
Control stack guard page temporarily disabled: proceed with caution

debugger invoked on a SB-KERNEL::CONTROL-STACK-EXHAUSTED in thread
#<THREAD "main thread" RUNNING {10005604C3}>:
  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.

Type HELP for debugger help, or (SB-EXT:EXIT) to exit from SBCL.

restarts (invokable by number or by possibly-abbreviated name):
  0: [RETRY                        ] Retry
                                     compiling #<CL-SOURCE-FILE "serapeum" "level2" "range">.
  1: [ACCEPT                       ] Continue, treating
                                     compiling #<CL-SOURCE-FILE "serapeum" "level2" "range">
                                     as having been successful.
  2:                                 Retry ASDF operation.
  3: [CLEAR-CONFIGURATION-AND-RETRY] Retry ASDF operation after resetting the
                                     configuration.
  4:                                 Retry ASDF operation.
  5:                                 Retry ASDF operation after resetting the
                                     configuration.
  6: [ABORT                        ] Give up on "serapeum"
  7:                                 Exit debugger, returning to top level.

(SB-KERNEL::CONTROL-STACK-EXHAUSTED-ERROR)
0] :backtrace

Backtrace for: #<SB-THREAD:THREAD "main thread" RUNNING {10005604C3}>
0: (SB-KERNEL::CONTROL-STACK-EXHAUSTED-ERROR)
1: ("foreign function: call_into_lisp")
2: ("foreign function: post_signal_tramp")
3: (MAKE-BUCKET :INVALID-VALUE-FOR-UNESCAPED-REGISTER-STORAGE :INVALID-VALUE-FOR-UNESCAPED-REGISTER-STORAGE) [optional]
4: (MAKE-BUCKET (((ARRAY-INDEX ARRAY-INDEX NON-NEGATIVE-INTEGER) (GO #:TAG2)) ((NON-NEGATIVE-INTEGER NON-NEGATIVE-INTEGER NON-NEGATIVE-INTEGER) (GO #:TAG3)) ((INTEGER INTEGER INTEGER) (GO #:TAG4)) ((RATIO RATIONAL RATIONAL) (GO #:TAG5)) ((RATIONAL RATIO RATIONAL) (GO #:TAG6)) ((RATIONAL RATIONAL RATIO) (GO #:TAG7)) ((RATIONAL FLOAT FLOAT) (GO #:TAG13)) ((RATIONAL FLOAT RATIONAL) (GO #:TAG14)) ((RATIONAL RATIONAL FLOAT) (GO #:TAG15)) ((SINGLE-FLOAT SINGLE-FLOAT SINGLE-FLOAT) (GO #:TAG8)) ((DOUBLE-FLOAT DOUBLE-FLOAT DOUBLE-FLOAT) (GO #:TAG9)) ((SHORT-FLOAT SHORT-FLOAT SHORT-FLOAT) (GO #:TAG10)) ...) ((ARRAY-INDEX ARRAY-INDEX NON-NEGATIVE-INTEGER) (GO #:TAG2)))
5: (MAKE-BUCKET (((ARRAY-INDEX ARRAY-INDEX NON-NEGATIVE-INTEGER) (GO #:TAG2)) ((NON-NEGATIVE-INTEGER NON-NEGATIVE-INTEGER NON-NEGATIVE-INTEGER) (GO #:TAG3)) ((INTEGER INTEGER INTEGER) (GO #:TAG4)) ((RATIO RATIONAL RATIONAL) (GO #:TAG5)) ((RATIONAL RATIO RATIONAL) (GO #:TAG6)) ((RATIONAL RATIONAL RATIO) (GO #:TAG7)) ((RATIONAL FLOAT FLOAT) (GO #:TAG13)) ((RATIONAL FLOAT RATIONAL) (GO #:TAG14)) ((RATIONAL RATIONAL FLOAT) (GO #:TAG15)) ((SINGLE-FLOAT SINGLE-FLOAT SINGLE-FLOAT) (GO #:TAG8)) ((DOUBLE-FLOAT DOUBLE-FLOAT DOUBLE-FLOAT) (GO #:TAG9)) ((SHORT-FLOAT SHORT-FLOAT SHORT-FLOAT) (GO #:TAG10)) ...) ((ARRAY-INDEX ARRAY-INDEX NON-NEGATIVE-INTEGER) (GO #:TAG2)))
6: (MAKE-BUCKET (((ARRAY-INDEX ARRAY-INDEX NON-NEGATIVE-INTEGER) (GO #:TAG2)) ((NON-NEGATIVE-INTEGER NON-NEGATIVE-INTEGER NON-NEGATIVE-INTEGER) (GO #:TAG3)) ((INTEGER INTEGER INTEGER) (GO #:TAG4)) ((RATIO RATIONAL RATIONAL) (GO #:TAG5)) ((RATIONAL RATIO RATIONAL) (GO #:TAG6)) ((RATIONAL RATIONAL RATIO) (GO #:TAG7)) ((RATIONAL FLOAT FLOAT) (GO #:TAG13)) ((RATIONAL FLOAT RATIONAL) (GO #:TAG14)) ((RATIONAL RATIONAL FLOAT) (GO #:TAG15)) ((SINGLE-FLOAT SINGLE-FLOAT SINGLE-FLOAT) (GO #:TAG8)) ((DOUBLE-FLOAT DOUBLE-FLOAT DOUBLE-FLOAT) (GO #:TAG9)) ((SHORT-FLOAT SHORT-FLOAT SHORT-FLOAT) (GO #:TAG10)) ...) ((ARRAY-INDEX ARRAY-INDEX NON-NEGATIVE-INTEGER) (GO #:TAG2)))

Errors in tests

I have a bunch of LOCAL macroexpansion errors when running the tests:

 Running test suite INTERNAL-DEFINITIONS
  Running test INTERNAL-DEFINITIONS ............
  Running test LET-OVER-DEF ..
  Running test LET-OVER-DEF-VS-HOISTING .
  Running test SYMBOL-MACROLET-SCOPE .
  Running test SYMBOL-MACRO-BEFORE-MACRO .
  Running test EXPR-ENV .
  Running test REDEFINING-FUNCTIONS .
; in: LAMBDA ()
;     (SERAPEUM:LOCAL
;       (SETQ SERAPEUM.TESTS::X (SERAPEUM.TESTS::M))
;       (DEFMACRO SERAPEUM.TESTS::M () 2)
;       SERAPEUM.TESTS::X)
; 
; caught ERROR:
;   during macroexpansion of
;   (LOCAL
;     (SETQ #)
;     (DEFMACRO M # ...)
;     ...).
;   Use *BREAK-ON-SIGNALS* to intercept.
;   
;    Macro definitions in `local' must precede other expressions.
;   Offender: M

;     (LET (SERAPEUM.TESTS::X)
;       (FLET ((SERAPEUM.TESTS::M ()
;                1))
;         (SERAPEUM:LOCAL
;           (SETQ SERAPEUM.TESTS::X #)
;           (DEFMACRO SERAPEUM.TESTS::M () 2)
;           SERAPEUM.TESTS::X)))
; 
; caught STYLE-WARNING:
;   The variable X is defined but never used.

Complete full definition for whitespacep?

AKA, code 0-31 are invisible char of ASCII alphabet, however not all of them are included in whitespacep which is against intuition especially the \Nul isn't considerred whitespace.

So, maybe extending whitespacep to cover all char whose code from 0 below 32 are more reasonable for whitespace ?

STABLE-SORT of reader literal

In types.lisp, the symbol *vref-by-type* is initialized like this:

(defparameter *vref-by-type*
  (stable-sort
   '((simple-bit-vector . sbit)
     (bit-vector . bit)
     (string . char)
     (simple-string . schar)
     (simple-vector . svref)
     (t . aref))
   #'proper-subtype-p
   :key #'car))

Since STABLE-SORT is a destructive operation, invoking it on a reader
literal is undefined and sbcl 1.5.7 issues a warning when compiling
this code. The simplest fix is to switch to:

(defparameter *vref-by-type*
  (stable-sort
   (list '(simple-bit-vector . sbit)
         '(bit-vector . bit)
         '(string . char)
         '(simple-string . schar)
         '(simple-vector . svref)
         '(t . aref))
   #'proper-subtype-p
   :key #'car))

Which sorts a freshly-consed list.

Spurious SBCL warning

SBCL seems to be inferring that DROP-WHILE returns an array when its argument type is unknown? Haven't debug further yet but wanted to record here now.

XILINX> (lambda (x) (rest (drop-while #'identity x)))
; in: LAMBDA (X)
;     (REST (DROP-WHILE #'IDENTITY XILINX::X))
; ==>
;   (CDR (DROP-WHILE #'IDENTITY XILINX::X))
; 
; caught STYLE-WARNING:
;   Derived type of
;     (SB-KERNEL:VECTOR-SUBSEQ* SB-C::SEQ SB-C::START SB-C::END)
;   in
;     (DROP-WHILE #'IDENTITY X)
;   is
;     (VALUES (SIMPLE-ARRAY * (*)) &OPTIONAL),
;   conflicting with their asserted type
;     LIST.
;   See also:
;     The SBCL Manual, Node "Handling of Types"
; 
; compilation unit finished
;   caught 1 STYLE-WARNING condition
#<FUNCTION (LAMBDA (X)) {52A66EBB}>

some naming-conventions

predicate-functions with - inside normally have also a - before the p
so string-containsp should be string-contains-p and string-tokenp should be string-token-p

Off-by-one in DEFINE-REAL-RANGE

Expected:

(range -1/4 2/4 2/4) => #(-1/4 1/4)

Actual:

(range -1/4 2/4 2/4) => #(-1/4)

Relevant expression is on line 189 of range.lisp:

(floor (abs (/ (- stop start) step)))

Changing it to (ceiling (abs (/ (- stop start) step))) yields the expected value, though I haven't exhaustively tested it beyond some poking in the repl.

Multi-level sorting

A function to compose multiple sorting predicates for multi-level sorting (e.g. by last name and first name).

Need to work out how or if to handle key functions, however.

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.