Skip to content

Commit

Permalink
v2.1.0 added automatically generated docs
Browse files Browse the repository at this point in the history
  • Loading branch information
inconvergent committed May 4, 2022
1 parent a477cbf commit f5b1852
Show file tree
Hide file tree
Showing 13 changed files with 14,344 additions and 24 deletions.
14,210 changes: 14,210 additions & 0 deletions DOCS.md

Large diffs are not rendered by default.

8 changes: 5 additions & 3 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ reduction operations.
VEQ was written to be the vector library used in my generative art library
[weird](https://github.com/inconvergent/weird).

## Examples
## Examples and Documentation

Here are some examples of use:

Expand Down Expand Up @@ -56,9 +56,11 @@ For more examples go to [examples](examples/ex.lisp).

You can also see some usagee in the [tests](test/veq.lisp).

## Versions Issues and feature requests
See [docs](DOCS.md) for automatically generated symbol documentation.

The most recent stable version is v2.0.3.
## Versions, Issues and feature requests

The most recent stable version is v2.1.0.

This code is still immature, and the interface might change in the future.

Expand Down
18 changes: 18 additions & 0 deletions docs.sh
Original file line number Diff line number Diff line change
@@ -0,0 +1,18 @@
#!/bin/bash

set -e
touch ./veq.asd
sbcl --quit \
--eval '(load "~/quicklisp/setup.lisp")'\
--eval '(ql:quickload :veq)'\
--eval '(handler-case (veq:ext-symbols? :pretty)
(error (c) (print c) (sb-ext:quit :unix-status 2)))'\
>DOCS.md.tmp 2>&1

cat << EOF > DOCS.md
# VEQ DOCUMENTATION
## Symbols
EOF

tail -n +17 DOCS.md.tmp >> DOCS.md
10 changes: 7 additions & 3 deletions src/array-broadcast.lisp
Original file line number Diff line number Diff line change
Expand Up @@ -14,16 +14,20 @@
(awg (arr arr-out)
(labels ((fxarg (s) (and (symbolp s) (not (eq s :va))))
(-varg (l) (remove-if-not #'fxarg (awf l))))
`(fvprogn (export ',exportname)
(def* ,exportname (,arr ,@br-arg)
(let ((docs (format nil "broadcast for fx: ~a~%macroname: ~a~%~%"
(mkstr fxname) (mkstr exportname))))
`(fvprogn (export ',exportname)
(map-docstring ',exportname ,docs)
(def* ,exportname (,arr ,@br-arg)
(declare #.*opt* (,(arrtype type) ,arr))
,docs
(,(veqsymb 1 type "WITH-ARRAYS")
(:itr k :n (/ (length ,arr) ,dim)
:arr ((,arr ,dim ,arr) ,@(if out `((,arr-out ,out))))
:fxs ((fx (,@arr-arg) (,fxname ,@(-varg arr-arg)
,@(-varg br-arg))))
:exs ((,(if out arr-out arr) k (fx ,arr))))
,(if out arr-out arr)))))))
,(if out arr-out arr))))))))

(defmacro make-broadcast-ops (typedim fxs &optional destructive)
(labels ((make (dim type)
Expand Down
3 changes: 3 additions & 0 deletions src/easing.lisp
Original file line number Diff line number Diff line change
Expand Up @@ -17,11 +17,14 @@
(num-types
`(fvprogn (export ',in) (export ',out) (export ',inout)
(defun ,in ,args
,(format nil "ease in:~%arg: ~a~%body: ~a" args (car body))
(let ((,x* (,(veqsymb 1 type "CLAMP") ,x*))) ,@body))
(defun ,out ,args
,(format nil "ease out:~%arg: ~a~%body: ~a" args (car body))
(let ((,x* (,(veqsymb 1 type "CLAMP") (- 1 ,x*))))
(1+ (- ,@body))))
(defun ,inout ,args
,(format nil "ease in-out:~%arg: ~a~%body: ~a" args (car body))
(let ((,x* (,(veqsymb 1 type "CLAMP") ,x*)))
(if (< ,x* 1/2) (let ((,x* (* 2 ,x*))) (* 1/2 ,@body))
(let ((,x* (- 1 (* 2 (- ,x* 1/2)))))
Expand Down
8 changes: 6 additions & 2 deletions src/macros.lisp
Original file line number Diff line number Diff line change
Expand Up @@ -90,8 +90,12 @@ did you load :veq multiple times?~%")
(defmacro lst (&body body)
"wrap (values ..) in (list ..)"
`(mvc #'list ,@body))
(defmacro from-lst (v) `(apply #'values ,v))
(defmacro ~ (&rest rest) `(mvc #'values ,@rest))
(defmacro from-lst (l)
"get values from list"
`(apply #'values ,l))
(defmacro ~ (&rest rest)
"wraps arguments in (mvc #'values ...)"
`(mvc #'values ,@rest))


;;;;;;;;;;;;;;;;;; MACRO UTILS
Expand Down
3 changes: 3 additions & 0 deletions src/mat-inv.lisp
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@
`(progn (export ',exportname)
(defun ,exportname (a)
(declare #.*opt* (,(arrtype type) a))
"invert 2x2 matrix"
(let ((inv (/ (- (* (aref a 0) (aref a 3))
(* (aref a 1) (aref a 2))))))
(declare (,type inv))
Expand All @@ -21,6 +22,7 @@
`(progn (export ',exportname)
(defun ,exportname (,a)
(declare #.*opt* (,(arrtype type) ,a))
"invert 3x3 matrix"
(let* ((,a00 (aref ,a 0)) (,a01 (aref ,a 1)) (,a02 (aref ,a 2))
(,a10 (aref ,a 3)) (,a11 (aref ,a 4)) (,a12 (aref ,a 5))
(,a20 (aref ,a 6)) (,a21 (aref ,a 7)) (,a22 (aref ,a 8))
Expand Down Expand Up @@ -49,6 +51,7 @@
`(progn (export ',exportname)
(defun ,exportname (,a)
(declare #.*opt* (,(arrtype type) ,a))
"invert 4x4 matrix"
(let* ((,a00 (aref ,a 0)) (,a01 (aref ,a 1)) (,a02 (aref ,a 2)) (,a03 (aref ,a 3))
(,a10 (aref ,a 4)) (,a11 (aref ,a 5)) (,a12 (aref ,a 6)) (,a13 (aref ,a 7))
(,a20 (aref ,a 8)) (,a21 (aref ,a 9)) (,a22 (aref ,a 10)) (,a23 (aref ,a 11))
Expand Down
9 changes: 8 additions & 1 deletion src/mat.lisp
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@
`(fvprogn
(let ((,',mm ,,m))
(declare (,',(arrtype type) ,',mm))
"multiply mat * v, use transpose to transmose mat"
(fvlet ((vv ,',dim (mvc #'values ,@,v)))
,',(cons 'values
(loop for i from 0 below dim
Expand All @@ -37,6 +38,7 @@
`(progn (export ',exportname)
(defun ,exportname (&optional (v ,(coerce 1 type)))
(declare #.*opt* (,type v))
"return eye matrix for dimension"
(the ,(arrtype type) (make-array ,(* dim dim)
:initial-contents (list ,@(eye))
:adjustable nil
Expand All @@ -63,6 +65,7 @@
(let ((exportname (veqsymb dim type "mt!")))
`(progn (export ',exportname)
(defmacro ,exportname (,a)
"transpose matrix of type ~a in-place"
`(let ((,',arr ,,a))
(declare (,',(arrtype type) ,',arr))
,',(cons 'progn (rotate))
Expand All @@ -82,6 +85,8 @@
(let ((exportname (veqsymb dim type (format nil "m~:[~;t~]m~:[~;t~]" ta tb))))
`(fvprogn (export ',exportname)
(defmacro ,exportname (,a* ,b*)
,(format nil "multiply ~:[mat~;(transpose mat)~] * ~:[mat~;(transpose mat)~]~%of type: ~a"
ta tb (arrtype type))
`(let* ((,',a ,,a*)
(,',b ,,b*)
(,',c (,',(veqsymb dim type "$zero") ,,dim)))
Expand Down Expand Up @@ -112,6 +117,7 @@
`(progn (export ',exportname)
(fvdef* ,exportname ((varg ,dim x))
(declare #.*opt* (,type x))
"make transpose matrix for moving by x"
(let ((res (,(veqsymb (1+ dim) type "meye"))))
(declare (,(arrtype type) res))
,@(loop for i from 1 to dim
Expand All @@ -127,6 +133,7 @@
`(progn (export ',exportname)
(fvdef* ,exportname ((varg ,dim x))
(declare #.*opt* (,type x))
"create matrix for scaling by x"
(let ((res (,(veqsymb (1+ dim) type "meye"))))
(declare (,(arrtype type) res))
,@(loop for i from 0 below dim
Expand All @@ -146,7 +153,7 @@
`(progn (export ',exportname)
(def* ,exportname (a)
(declare #.*opt* (,type a))
"create 2d rotation matrix for rotating a rad"
"create 2d rotation matrix for rotating a rads"
(let ((cosa (cos a)) (sina (sin a)))
(declare (,type cosa sina))
(f_ (list cosa (- sina) ,@(if w `(,z0)) sina cosa
Expand Down
1 change: 1 addition & 0 deletions src/packages.lisp
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@
#:*eps*

#:v? #:d? #:i?
#:context? #:ext-symbols?

#:mac #:mac*
#:ffl #:dfl
Expand Down
7 changes: 5 additions & 2 deletions src/select-dim.lisp
Original file line number Diff line number Diff line change
Expand Up @@ -9,10 +9,13 @@
(symb (map 'list #'symb string-symb))
(vals `(values ,@symb))
(ign `(ignore ,@(set-difference '(x y z w) symb)))
(typ `(,type ,@symb)))
(typ `(,type ,@symb))
(docs (format nil "macro. reorder arguments (X Y Z W) as ~a, ~a.~%" symb ign)))
`(progn (export ',exportname)
(map-docstring ',exportname ,docs :nodesc)
(defmacro ,exportname (&rest ,rest)
`(multiple-value-bind (x y z w) (mvc #'values ,@,rest)
,docs
`(mvb (x y z w) (mvc #'values ,@,rest)
(declare ,',typ ,',ign)
,',vals))))))

Expand Down
5 changes: 3 additions & 2 deletions src/utils.lisp
Original file line number Diff line number Diff line change
Expand Up @@ -42,11 +42,12 @@


(defun v? (&optional (silent t))
"get version. use silent to surpress stdout"
(let ((v (slot-value (asdf:find-system 'weird) 'asdf:version)))
(unless silent (format t "~%veq version: ~a~%" v))
v))
(defun d? (f) (describe f))
(defun i? (f) (inspect f))
(defun d? (f) "describe argument" (describe f))
(defun i? (f) "inspect argument" (inspect f))



Expand Down
84 changes: 74 additions & 10 deletions src/veq.lisp
Original file line number Diff line number Diff line change
Expand Up @@ -3,15 +3,73 @@

(defparameter *errmsg* "~%-------------~% error in ~a: ~a ~%~%")

(declaim (list *symbols-map*))
(defvar *symbols-map* '())
(declaim (list *symbols-map* *docstring-map*))
(defvar *symbols-map* (list))
(defvar *docstring-map* (list))

(defmacro veq? ()
"list all macrolets in veq context"
`(list ,@(sort (mapcar (lambda (s) (mkstr (car s)))
*symbols-map*)
#'string-lessp)))

(defmacro context? ()
"list all macrolets in veq context. that is ops available inside vprog,
fvprogn, vdef, fvdef defined contexts/functions."
(awg (s)
`(list (sort (mapcar (lambda (,s) (mkstr (car ,s)))
,*symbols-map*)
#'string-lessp))))

(defun select-docs (s)
(let* ((docs (find-if (lambda (c) (equal s c))
*docstring-map*
:key #'car))
(idocs (documentation s 'function))
(desc (if (find :nodesc docs) nil
(with-output-to-string (*standard-output*)
(describe s)))))

(cond (docs (format nil "```~%~a~@[~%~a~]```" (cadr docs) desc))
(idocs (format nil "```~%~a~@[~%~a~]```" idocs desc))
(t (format nil "```~%:missing:~%~@[~%~a~]```" desc)))))

(defmacro pckgs ()
(awg (s)
`(sort (loop for ,s being the external-symbols of (find-package :veq)
collect (list (mkstr ,s) ,s))
#'string-lessp
:key #'car)))

(defmacro ext-symbols? (&optional mode)
"list all external symbols in veq. use :verbose to inlcude docstring. use
:pretty to print verbose output to stdout in a readable form."
(awg (str s)
(case mode
(:pretty
`(loop for (,str ,s) in (pckgs)
do (format t "~&### ~a~%~%~a~&"
,str (select-docs ,s))))
(:pairs
`(loop for (,str ,s) in (pckgs) collect (list ,str (select-docs ,s))))
(otherwise
`(loop for (,str ,s) in (pckgs) collect ,str)))))

(defun map-docstring (&rest pair)
(setf *docstring-map*
(remove-if (lambda (cand) (equal (car cand) (car pair)))
*docstring-map*))
(push pair *docstring-map*))

(map-docstring 'vref
(mkstr "use (veq:vref s x) or (:vr s x) to get dim x of symbol s"
#\Newline
"in fvdef*, vdef*, def*. see replace-varg for details")
:nodesc)

(map-docstring 'varg
(mkstr "use (veq:varg n a b ...) or (:vr n a b ...) to represent vectors a,b "
#\Newline
"of dim n in fvdef*, vdef*, def*. see replace-varg for details")
:nodesc)


; TODO: clean up this mess
(defun map-symbol (pair)
(declare #.*opt* (list pair))
"add pair macrolet pair. see macro.lisp"
Expand Down Expand Up @@ -40,6 +98,8 @@
(in . "IVEC") (nil . ""))))))
"VEQ")))

; ---------------- REGISTER BASIC OPS

(defun optype (symb)
(declare #.*opt*)
"use first letter to select type d -> df, f -> ff"
Expand All @@ -50,13 +110,17 @@
(declare (symbol mname) (list args))
"build an op. see ops-1.lisp, ops-2.lisp, ..."
(let* ((declares `(,(optype mname) ,@args))
(fname (symb "-" mname)))
(fname (symb "-" mname))
(docs (format nil "veq context op: ~a~%fxname: ~a~%args: ~a~%body: ~a~%"
(mkstr mname) (mkstr fname) (mkstr args ) (mkstr (car body)))))
`(progn (map-symbol `(,',mname (&body body)
`(mvc #',',',fname ,@body)))
(map-docstring ',mname ,docs :nodesc)
(export ',mname)
,@(unless #.*dev* `((declaim (inline ,fname))))
(defun ,fname ,args (declare ,*opt* ,declares)
(progn ,@body)))))
,docs
(progn ,@body)))))

(defun type-placeholder (root type)
(labels ((repl (symb type)
Expand All @@ -70,7 +134,7 @@
(type-placeholder (cdr root) type))))))

(defmacro ops (&body body)
"build ops in ops-1.lisp, ops-2.lisp, ..."
"used to build ops in ops-1.lisp, ops-2.lisp, ..."
`(progn ,@(loop for (args body*) in (group (type-placeholder body #\D) 2)
collect `(op ,args ,body*))
,@(loop for (args body*) in (group (type-placeholder body #\F) 2)
Expand Down
2 changes: 1 addition & 1 deletion veq.asd
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
(asdf:defsystem #:veq
:description "reasonably fast operations for 1-4d vectors, matrices, and
arrays of vectors."
:version "2.0.3"
:version "2.1.0"
:author "anders hoff / @inconvergent / [email protected]"
:licence "MIT"
:in-order-to ((asdf:test-op (asdf:test-op #:veq/tests)))
Expand Down

0 comments on commit f5b1852

Please sign in to comment.