Package COM.INFORMATIMAGO.COMMON-LISP.CESARUM.UTILITY


This package exports some utility & syntactic sugar functions and macros.



License:

    AGPL3

    Copyright Pascal J. Bourguignon 2003 - 2016

    This program is free software: you can redistribute it and/or modify
    it under the terms of the GNU Affero General Public License as published by
    the Free Software Foundation, either version 3 of the License, or
    (at your option) any later version.

    This program is distributed in the hope that it will be useful,
    but WITHOUT ANY WARRANTY; without even the implied warranty of
    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
    GNU Affero General Public License for more details.

    You should have received a copy of the GNU Affero General Public License
    along with this program.
    If not, see <http://www.gnu.org/licenses/>

(+epsilon float)
function
Returns the float incremented by the smallest increment possible.
(-epsilon float)
function
Returns the float incremented by the smallest increment possible.

/APPLY

/NTH-ARG

(compose &rest functions)
macro
RETURN:     The functional composition of the FUNCTIONS.
EXAMPLE:    (compose abs sin cos) = (lambda (&rest args) (abs (sin (apply (function cos) args))))
NOTE:       (compose) = (function identity)
            (compose foo) = (function foo)
(compose-and-call &rest functions-and-arg)
macro
DO:         Call the functional composition of the functions, on the
            argument.
EXAMPLE:    (compose-and-call abs sin cos 0.234) --> 0.8264353

COMPUTE-CLOSURE

CONCAT

(copy-hash-table table)
function
TABLE:  (OR NULL HASH-TABLE)
RETURN: If TABLE is NIL, then NIL,
        else a new HASH-TABLE with the same TEST, SIZE, REHASH-THRESHOLD
        REHASH-SIZE and KEY->VALUE associations than TABLE.
        (Neither the keys nor the values are copied).

CURRY

(defenum name-and-options &rest constants)
macro
Define an named enumeration type, a set of constants with integer
values, and a label function to produce the name of the constants from
the numerical value.

NAME-AND-OPTIONS:

            The name of the enum type, or a list containing the name
            of the enum type and options (no option defined so far).
            The label function defined is named <enum-type-name>-LABEL

CONSTANTS:  The first element of CONSTANTS may be an optional docstring.
            Each constant is either a symbol naming the constant of the enum,
            (the value is then the successor of the previous value),
            or a list containing the constant name and the constant value.
(define-if-undefined &rest definitions)
macro
Use this to conditionally define functions, variables, or macros that
may or may not be pre-defined in this Lisp.  This can be used to provide
CLtL2 compatibility for older Lisps.
WHO'S THE AUTHOR?
(define-structure-class name-and-options &rest doc-and-slots)
macro
DO:     Define a class implementing the structure API.
        This macro presents the same API as DEFSTRUCT, but instead of
        defining a structure, it defines a class, and the same functions
        as would be defined by DEFSTRUCT.

        The option :TYPE accepts LIST, VECTOR or STRUCTURE.
        When given, it falls back to CL:DEFSTRUCT.
        The DEFSTRUCT option :INITIAL-OFFSET is only supported
        when :TYPE is given.
(define-with-object class-name slots)
macro
DO:       Define a macro: (WITH-{CLASS-NAME} object &body body)
          expanding to:   (with-slots ({slots}) object @body)
(define-with-structure name-and-options &rest slots)
macro
NAME-AND-OPTIONS:  Either a structure name or a list (name . options).
          Valid options are: (:conc-name prefix).
DO:       Define a macro: (WITH-{NAME} object &body body)
          expanding to a symbol-macrolet embedding body where
          symbol macros are defined to access the slots.
(dichotomy matchp start end)
function

MATCHP: A function taking an integer between [START,END[, and
        returning an order (signed integer).
START:  The minimum integer.
END:    The maximum integer+1.
RETURN: (values found index order)
POST:	(<= start index (1- end))
        +-------------------+----------+-------+----------+
        | Case              |  found   | index |  order   |
        +-------------------+----------+-------+----------+
        | x < a[i]          |   FALSE  | start |  less    |
        | a[i] < x < a[i+1] |   FALSE  |   i   |  greater |
        | x = a[i]          |   TRUE   |   i   |  equal   |
        | a[max] < x        |   FALSE  | end-1 |  greater |
        +-------------------+----------+-------+----------+
(dichotomy-search vector value compare &key start end key)
function
PRE:	entry is the element to be searched in the table.
        (<= start end)
RETURN: (values found index order)
POST:	(<= start index end)
        +-------------------+----------+-------+----------+
        | Case              |  found   | index |  order   |
        +-------------------+----------+-------+----------+
        | x < a[min]        |   FALSE  |  min  |  less    |
        | a[i] < x < a[i+1] |   FALSE  |   i   |  greater |
        | x = a[i]          |   TRUE   |   i   |  equal   |
        | a[max] < x        |   FALSE  |  max  |  greater |
        +-------------------+----------+-------+----------+
(distinct-float-types)
function
RETURN: a subset of (long-float double-float single-float short-float)
that represents the partition of the float type for this
implementation.

There can be fewer than four internal representations for floats. If
there are fewer distinct representations, the following rules apply:

  • If there is only one, it is the type single-float. In this
    representation, an object is simultaneously of types single-float,
    double-float, short-float, and long-float.

  • Two internal representations can be arranged in either of the
    following ways:

      □ Two types are provided: single-float and short-float. An
        object is simultaneously of types single-float,  double-float,
        and long-float.

      □ Two types are provided: single-float and double-float. An
        object is simultaneously of types single-float and
        short-float, or double-float and long-float.

  • Three internal representations can be arranged in either of the
    following ways:

      □ Three types are provided: short-float, single-float, and
        double-float. An object can simultaneously be of  type
        double-float and long-float.

      □ Three types are provided: single-float, double-float, and
        long-float. An object can simultaneously be of  types
        single-float and short-float.

(eighth-arg x x x x x x x x &rest x)
function
RETURN: The eighth argument.
(equiv a b)
function
Return A ⇔ B
(extract-slots object slots)
generic-function
RETURN:         A plist slot values.
OBJECT:         A lisp object.
SLOTS:          A list of slot names.
(fifth-arg x x x x x &rest x)
function
RETURN: The fifth argument.

FIND-CYCLES

(find-shortest-path from to successors)
function
RETURN: The shortest path of length>0 from FROM to TO if it exists, or NIL.
(first-arg x &rest x)
function
RETURN: The first argument.
(float-ctypecase expression &body clauses)
macro
EXPRESSION: an expression evaluate to some value.

CLAUSES:    ctypecase clauses where the type is one of the standard
            FLOAT direct subtypes, ie. one of (SHORT-FLOAT
            SINGLE-FLOAT DOUBLE-FLOAT LONG-FLOAT).

NOTE:      Implementations may conflate the various subtypes of FLOAT.
           When two float types are conflated, some implementation
           will signal a warning on any typecase that have them in
           separate clauses.  Since they're the same type, we can as
           well remove the duplicate clauses.

SEE:       CLHS Type SHORT-FLOAT, SINGLE-FLOAT, DOUBLE-FLOAT, LONG-FLOAT

DO:        Expands to a CTYPECASE where only the clauses with unique
           float types are present.
(float-etypecase expression &body clauses)
macro
EXPRESSION: an expression evaluate to some value.

CLAUSES:    etypecase clauses where the type is one of the standard
            FLOAT direct subtypes, ie. one of (SHORT-FLOAT
            SINGLE-FLOAT DOUBLE-FLOAT LONG-FLOAT).

NOTE:      Implementations may conflate the various subtypes of FLOAT.
           When two float types are conflated, some implementation
           will signal a warning on any typecase that have them in
           separate clauses.  Since they're the same type, we can as
           well remove the duplicate clauses.

SEE:       CLHS Type SHORT-FLOAT, SINGLE-FLOAT, DOUBLE-FLOAT, LONG-FLOAT

DO:        Expands to a ETYPECASE where only the clauses with unique
           float types are present.
(float-typecase expression &body clauses)
macro
EXPRESSION: an expression evaluate to some value.

CLAUSES:    typecase clauses where the type is one of the standard
            FLOAT direct subtypes, ie. one of (SHORT-FLOAT
            SINGLE-FLOAT DOUBLE-FLOAT LONG-FLOAT).

NOTE:      Implementations may conflate the various subtypes of FLOAT.
           When two float types are conflated, some implementation
           will signal a warning on any typecase that have them in
           separate clauses.  Since they're the same type, we can as
           well remove the duplicate clauses.

SEE:       CLHS Type SHORT-FLOAT, SINGLE-FLOAT, DOUBLE-FLOAT, LONG-FLOAT

DO:        Expands to a TYPECASE where only the clauses with unique
           float types are present.
(for (var first last &optional (step NIL stepp)) &body body)
macro
For loop.
DO:    Repeat BODY with VAR bound to successive integer values from
       FIRST to LAST inclusive.
       If the optional STEP argument is abstent, then it is taken as 1 or -1
       depending on the order of FIRST and LAST.
       VAR is incremented by STEP and it stops when VAR goes above
       or below LAST depending on the sign of STEP.
(fourth-arg x x x x &rest x)
function
RETURN: The fourth argument.
(functional-pipe &body forms)
macro
Execute forms in sequence each in a lexical scope where *, ** and *** are bound
to the results of the last three previous forms.
Return the results of the last form.
(gen-extract-slots ovar slots)
function
SEE:            PRINT-PARSEABLE-OBJECT
RETURN:         A form building a plist of slot values.
(handling-errors &body body)
macro
DO:       Execute the BODY with a handler for CONDITION and
          SIMPLE-CONDITION reporting the conditions.
(hash-table-entries table)
function
Returns an a-list of the entries (key . val) in the TABLE.
(hash-table-keys table)
function
Returns a list of the keys in the TABLE.
(hash-table-path table &rest keys)
function
Given a hash-table that may contain other hash-table, walks down
the path of KEYS, returning the ultimate value
(hash-table-select predicate table)
function
RETURN: An a-list of  (k . v) from the TABLE
        such as (funcall PREDICATE k v) is true.
(hash-table-to-sexp table)
function
Returns a sexp containing the hash-table data.
(hash-table-values table)
function
Returns a list of the values in the TABLE.
(hashtable &key test size rehash-size rehash-threshold elements)
function
Creates a new hash-table, filled with the given ELEMENTS.
ELEMENTS must be a list of lists of two items, the key and the value.
Note: we use the name HASHTABLE to avoid name collision.
(imply p q)
function
Return P ⇒ Q
(include-file path)
function
NOTE:    Untasty, but sometimes useful.
DO:      Read from the file at PATH all the sexps and returns a list of them
         prefixed with 'progn.
USAGE:   #.(include-file "source.lisp")
(map-into-hash-table sequence &key key value test size rehash-size rehash-threshold)
function
Creates a new hash-table, filled with the associations obtained by
applying the function KEY and the function VALUE on each element of
the SEQUENCE.
The other key parameter are passed to MAKE-HASH-TABLE.
(maximize predicate list)
function
RETURN: The maximum value and the item in list for which predicate
         is the maximum.
(ninth-arg x x x x x x x x x &rest x)
function
RETURN: The ninth argument.
(nsubseq sequence start &optional end)
function
RETURN:  When the SEQUENCE is a vector, the SEQUENCE itself, or a dispaced
         array to the SEQUENCE.
         When the SEQUENCE is a list, it may destroy the list and reuse the
         cons cells to make the subsequence.
(nth-arg n &rest arguments)
function
RETURN: The Nth argument following N.
(object-identity object)
function
RETURN:         A string containing the object identity as printed by
                PRINT-UNREADABLE-OBJECT.
(op-type-of symbol &optional env)
function
From: nikodemus@random-state.net
Newsgroups: comp.lang.lisp
Date: 29 Jul 2004 03:59:50 GMT
Message-ID: <ce9snm$4bp8o$1@midnight.cs.hut.fi>
(pjb-defclass name super &rest args)
macro
This macro encapsulate DEFCLASS and allow the declaration of the attributes
in a shorter syntax.
ARGS  is a list of s-expr, whose car is either :ATT (to declare an attribute)
      or :DOC to give the documentation string of the class.
      (:OPT ...) is not implemented yet.
      (:ATT name type [ init-value [doc-string] | doc-string ]) defines
      an attribute named NAME, of type TYPE, with the given initial value
      and documentation strings.  An accessor and an initarg keyword of
      same NAME are also defined.
(print-hashtable table &optional stream)
function
Prints readably the hash-table, using #. and the HASHTABLE function.
(print-parseable-object (object stream &key (type t) identity) &rest slots)
macro

DO:             Prints on the STREAM the object as a list.  If all the
                objects printed inside it are printed readably or with
                PRINT-PARSEABLE-OBJECT, then that list should be
                readable, at least with *READ-SUPPRESS* set to T.

OBJECT:         Either a variable bound to the object to be printed,
                or a binding list (VARNAME OBJECT-EXPRESSION), in
                which case the VARNAME is bound to the
                OBJECT-EXPRESSION during the evaluation of the SLOTS.

STREAM:         The output stream where the object is printed to.

TYPE:           If true, the class-name of the OBJECT is printed as
                first element of the list.

IDENTITY:       If true, the object identity is printed as a string in
                the last position of the list.

SLOTS:          A list of either a symbol naming the slot, or a list
                (name expression), name being included quoted in the
                list, and the expression being evaluated to obtain the
                value.

RETURN:         The object that bas been printed (so that you can use
                it in tail position in PRINT-OBJECT conformingly).

EXAMPLE:        (print-parseable-object (object stream :type t :identity t)
                  slot-1
                  (:slot-2 (thing-to-list (slot-2 object)))
                  slot-3)
(progn-concat forms)
function
DO:       Wraps the forms in a PROGN.  If they're PROGN forms,
          then their PROGN is unwrapped first.

RCURRY

(safe-apply fun &rest args)
function
DO:    Call APPLY or REDUCE depending on the length of ARGS.
NOTE:  No prefix argument are allowed for REDUCE!
       (safe-apply 'concatenate 'string list-of-sequence) doesn't work!
       Use instead:
       (safe-apply (lambda (a b) (concatenate 'string a b)) list-of-sequence)
(scase keyform &rest clauses)
macro
DO:         A CASE, but for string keys. That is, it uses STRING= as test
            instead of the ''being the same'' test.
(sconc &rest args)
macro
Concatenate strings.
(second-arg x x &rest x)
function
RETURN: The second argument.
(seventh-arg x x x x x x x &rest x)
function
RETURN: The seventh argument.
(sexp-to-hash-table sexp)
function
Create a new hash-table containing the data described in the sexp
(produced by HASH-TABLE-TO-SEXP.
(sign n)
function
RETURN: -1 if N is negative,
        +1 if N is positive,
         0 if N is 0.

SIMPLE-PROGRAM-ERROR

SIMPLE-PROGRAM-ERROR-FORMAT-ARGUMENTS

SIMPLE-PROGRAM-ERROR-FORMAT-CONTROL

(sixth-arg x x x x x x &rest x)
function
RETURN: The sixth argument.
sloted-object
class
This is a mixin class providing generic SLOTS and PRINT-OBJECT
methods.
Class precedence list: SLOTED-OBJECT STANDARD-OBJECT T
(slots-for-print object)
generic-function
This generic function collects a p-list describing the slots of the OBJECT.
The generic function EXTRACT-SLOTS can be used to build this p-list.
The APPEND method combination automatically appends the lists provided
by the SLOTS-FOR-PRINT methods on the various subclasses.
(tenth-arg x x x x x x x x x x &rest x)
function
RETURN: The tenth argument.
(third-arg x x x &rest x)
function
RETURN: The third argument.
(topological-sort nodes lessp)
function
RETURN: A list of NODES sorted topologically according to
        the partial order function LESSP.
        If there are cycles (discounting reflexivity),
        then the list returned won't contain all the NODES.
(tracing &body body)
macro
TRACE works only on non-CL functions.
This macro will work somewhat on any form in body.
(tracing-labels defs &body body)
macro
This macro is a replacement for LABELS that traces the calls of
the local functions.
(tracing-let clauses &body body)
macro
Like LET, but prints on the *trace-output* the value of the bindings.
(tracing-let* clauses &body body)
macro
Like LET*, but prints on the *trace-output* the value of the bindings.
(transitive-closure fun set &key test use)
function
FUN:     set --> P(set)
          x |--> { y }
SET:     A sequence.
TEST:    EQL, EQUAL or EQUALP
USE:     Either HASH-TABLE or LIST; specifies the data structure used for the intermediary sets.
RETURN:  A list containing closure of fun on the set.
EXAMPLE: (transitive-closure (lambda (x) (list (mod (* x 2) 5))) '(1)) --> (3 4 2 1)
NOTE:    This version avoids calling FUN twice with the same argument.
(undisplace-array array)
function
RETURN:  The fundamental array and the start and end positions into
         it of a displaced array.
AUTHOR:  Erik Naggum <erik@naggum.no>
(until condition &body body)
macro
Until loop.
(vector-init vector constructor)
function
DO:      Sets all the slots in vector to the successive results of
         the function CONSTRUCTOR called with integers from 0 up
s         to the dimension of the VECTOR.
RETURN:  VECTOR
(while condition &body body)
macro
While loop.

WITH-FUNCTIONS

(with-gensyms syms &body body)
macro
DO:      Replaces given symbols with gensyms. Useful for creating macros.
NOTE:    This version by Paul Graham in On Lisp.
(wsiosbp &body body)
macro
Like with-standard-io-syntax but with the current package.
The *PACKAGE* is kept bound to the current package.
(xor a b)
function
Return A ⊻ B