Fix modelines
[fiveam.git] / src / utils.lisp
1 ;;;; -*- Mode: Lisp; indent-tabs-mode: nil -*-
2
3 (in-package :it.bese.fiveam)
4
5 (defmacro dolist* ((iterator list &optional return-value) &body body)
6   "Like DOLIST but destructuring-binds the elements of LIST.
7
8 If ITERATOR is a symbol then dolist* is just like dolist EXCEPT
9 that it creates a fresh binding."
10   (if (listp iterator)
11       (let ((i (gensym "DOLIST*-I-")))
12         `(dolist (,i ,list ,return-value)
13            (destructuring-bind ,iterator ,i
14              ,@body)))
15       `(dolist (,iterator ,list ,return-value)
16          (let ((,iterator ,iterator))
17            ,@body))))
18
19 (defun make-collector (&optional initial-value)
20   "Create a collector function.
21
22 A Collector function will collect, into a list, all the values
23 passed to it in the order in which they were passed. If the
24 callector function is called without arguments it returns the
25 current list of values."
26   (let ((value initial-value)
27         (cdr (last initial-value)))
28     (lambda (&rest items)
29       (if items
30           (progn
31             (if value
32                 (if cdr
33                     (setf (cdr cdr) items
34                           cdr (last items))
35                     (setf cdr (last items)))
36                 (setf value items
37                       cdr (last items)))
38             items)
39           value))))
40
41 (defun partitionx (list &rest lambdas)
42   (let ((collectors (mapcar (lambda (l)
43                               (cons (if (and (symbolp l)
44                                              (member l (list :otherwise t)
45                                                      :test #'string=))
46                                         (constantly t)
47                                         l)
48                                     (make-collector)))
49                             lambdas)))
50     (dolist (item list)
51       (block item
52         (dolist* ((test-func . collector-func) collectors)
53           (when (funcall test-func item)
54             (funcall collector-func item)
55             (return-from item)))))
56     (mapcar #'funcall (mapcar #'cdr collectors))))
57
58 ;;;; ** Anaphoric conditionals
59
60 (defmacro if-bind (var test &body then/else)
61   "Anaphoric IF control structure.
62
63 VAR (a symbol) will be bound to the primary value of TEST. If
64 TEST returns a true value then THEN will be executed, otherwise
65 ELSE will be executed."
66   (assert (first then/else)
67           (then/else)
68           "IF-BIND missing THEN clause.")
69   (destructuring-bind (then &optional else)
70       then/else
71     `(let ((,var ,test))
72        (if ,var ,then ,else))))
73
74 (defmacro aif (test then &optional else)
75   "Just like IF-BIND but the var is always IT."
76   `(if-bind it ,test ,then ,else))
77
78 ;;;; ** Simple list matching based on code from Paul Graham's On Lisp.
79
80 (defmacro acond2 (&rest clauses)
81   (if (null clauses)
82       nil
83       (with-gensyms (val foundp)
84         (destructuring-bind ((test &rest progn) &rest others)
85             clauses
86           `(multiple-value-bind (,val ,foundp)
87                ,test
88              (if (or ,val ,foundp)
89                  (let ((it ,val))
90                    (declare (ignorable it))
91                    ,@progn)
92                  (acond2 ,@others)))))))
93
94 (defun varsymp (x)
95   (and (symbolp x) (eq (aref (symbol-name x) 0) #\?)))
96
97 (defun binding (x binds)
98   (labels ((recbind (x binds)
99              (aif (assoc x binds)
100                   (or (recbind (cdr it) binds)
101                       it))))
102     (let ((b (recbind x binds)))
103       (values (cdr b) b))))
104
105 (defun list-match (x y &optional binds)
106   (acond2
107     ((or (eql x y) (eql x '_) (eql y '_))
108      (values binds t))
109     ((binding x binds) (list-match it y binds))
110     ((binding y binds) (list-match x it binds))
111     ((varsymp x) (values (cons (cons x y) binds) t))
112     ((varsymp y) (values (cons (cons y x) binds) t))
113     ((and (consp x) (consp y) (list-match (car x) (car y) binds))
114      (list-match (cdr x) (cdr y) it))
115     (t (values nil nil))))
116
117 (defun vars (match-spec)
118   (let ((vars nil))
119     (labels ((find-vars (spec)
120                (cond
121                  ((null spec) nil)
122                  ((varsymp spec) (push spec vars))
123                  ((consp spec)
124                   (find-vars (car spec))
125                   (find-vars (cdr spec))))))
126       (find-vars match-spec))
127     (delete-duplicates vars)))
128
129 (defmacro list-match-case (target &body clauses)
130   (if clauses
131       (destructuring-bind ((test &rest progn) &rest others)
132           clauses
133         (with-gensyms (tgt binds success)
134           `(let ((,tgt ,target))
135              (multiple-value-bind (,binds ,success)
136                  (list-match ,tgt ',test)
137                (declare (ignorable ,binds))
138                (if ,success
139                    (let ,(mapcar (lambda (var)
140                                    `(,var (cdr (assoc ',var ,binds))))
141                                  (vars test))
142                      (declare (ignorable ,@(vars test)))
143                      ,@progn)
144                    (list-match-case ,tgt ,@others))))))
145       nil))
146
147 ;;;; * def-special-environment
148
149 (defun check-required (name vars required)
150   (dolist (var required)
151     (assert (member var vars)
152             (var)
153             "Unrecognized symbol ~S in ~S." var name)))
154
155 (defmacro def-special-environment (name (&key accessor binder binder*)
156                                   &rest vars)
157   "Define two macros for dealing with groups or related special variables.
158
159 ACCESSOR is defined as a macro: (defmacro ACCESSOR (VARS &rest
160 BODY)).  Each element of VARS will be bound to the
161 current (dynamic) value of the special variable.
162
163 BINDER is defined as a macro for introducing (and binding new)
164 special variables. It is basically a readable LET form with the
165 prorpe declarations appended to the body. The first argument to
166 BINDER must be a form suitable as the first argument to LET.
167
168 ACCESSOR defaults to a new symbol in the same package as NAME
169 which is the concatenation of \"WITH-\" NAME. BINDER is built as
170 \"BIND-\" and BINDER* is BINDER \"*\"."
171   (unless accessor
172     (setf accessor (format-symbol (symbol-package name) "~A-~A" '#:with name)))
173   (unless binder
174     (setf binder   (format-symbol (symbol-package name) "~A-~A" '#:bind name)))
175   (unless binder*
176     (setf binder*  (format-symbol (symbol-package binder) "~A~A" binder '#:*)))
177   `(eval-when (:compile-toplevel :load-toplevel :execute)
178      (flet ()
179        (defmacro ,binder (requested-vars &body body)
180          (check-required ',name ',vars (mapcar #'car requested-vars))
181          `(let ,requested-vars
182             (declare (special ,@(mapcar #'car requested-vars)))
183             ,@body))
184        (defmacro ,binder* (requested-vars &body body)
185          (check-required ',name ',vars (mapcar #'car requested-vars))
186          `(let* ,requested-vars
187             (declare (special ,@(mapcar #'car requested-vars)))
188             ,@body))
189        (defmacro ,accessor (requested-vars &body body)
190          (check-required ',name ',vars requested-vars)
191          `(locally (declare (special ,@requested-vars))
192             ,@body))
193        ',name)))
194
195 ;; Copyright (c) 2002-2006, Edward Marco Baringer
196 ;; All rights reserved.
197 ;;
198 ;; Redistribution and use in source and binary forms, with or without
199 ;; modification, are permitted provided that the following conditions are
200 ;; met:
201 ;;
202 ;;  - Redistributions of source code must retain the above copyright
203 ;;    notice, this list of conditions and the following disclaimer.
204 ;;
205 ;;  - Redistributions in binary form must reproduce the above copyright
206 ;;    notice, this list of conditions and the following disclaimer in the
207 ;;    documentation and/or other materials provided with the distribution.
208 ;;
209 ;;  - Neither the name of Edward Marco Baringer, nor BESE, nor the names
210 ;;    of its contributors may be used to endorse or promote products
211 ;;    derived from this software without specific prior written permission.
212 ;;
213 ;; THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
214 ;; "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
215 ;; LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
216 ;; A PARTICULAR PURPOSE ARE DISCLAIMED.  IN NO EVENT SHALL THE COPYRIGHT
217 ;; OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
218 ;; SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
219 ;; LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
220 ;; DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
221 ;; THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
222 ;; (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
223 ;; OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE