##// END OF EJS Templates
Remove cl-uglify-js
Remove cl-uglify-js

File last commit:

r23:ae42b3a9 default
r23:ae42b3a9 default
Show More
ps-macros.lisp
203 lines | 5.0 KiB | text/x-common-lisp | CommonLispLexer
100% parser, 100% macros, 50% intrinsics, 10% api, 0% misc
r1
(in-package sugar-qsp)
;;;; Parenscript macros which make the parser's intermediate
;;;; representation directly compilable by Parenscript
;;;; Some utility macros for other .ps sources too.
;;; Utils
(ps:defpsmacro defm (path args &body body)
`(setf ,path (lambda ,args ,@body)))
(ps:defpsmacro root (&rest path)
`(ps:@ *sugar-q-s-p ,@path))
Tutorial game works!
r6 (ps:defpsmacro in (key obj)
`(ps:chain ,obj (has-own-property ,key)))
Properly handle stringly-indexed arrays
r16 (ps:defpsmacro with-frame (&body body)
`(progn
(api-call push-local-frame)
(unwind-protect
,@body
(api-call pop-local-frame))))
100% parser, 100% macros, 50% intrinsics, 10% api, 0% misc
r1 ;;; Common
(defmacro defpsintrinsic (name)
`(ps:defpsmacro ,name (&rest args)
Tutorial game works!
r6 `(funcall (root lib ,',name)
100% parser, 100% macros, 50% intrinsics, 10% api, 0% misc
r1 ,@args)))
(defmacro defpsintrinsics (() &rest names)
`(progn ,@(loop :for name :in names
:collect `(defpsintrinsic ,name))))
(defpsintrinsics ()
Menu, game saving
r11 rand copyarr arrpos arrcomp instr isnum strcomp strfind strpos iif gosub func dynamic dyneval main-p main-pl main-nl maintxt main-clear stat-p stat-pl stat-nl stattxt stat-clear cls curacts addobj delobj killobj menu play isplay close closeall refint view rgb showinput usertxt cmdclear input openqst addqst killqst opengame savegame wait msecscount settimer)
100% parser, 100% macros, 50% intrinsics, 10% api, 0% misc
r1
(ps:defpsmacro api-call (func &rest args)
`(funcall (root api ,func) ,@args))
Properly handle stringly-indexed arrays
r16 (ps:defpsmacro label-block ((&key (locals t)) &body body)
Locals
r14 (let ((has-labels (some #'keywordp body)))
`(block nil
,@(when has-labels
'((defvar __labels)))
Properly handle stringly-indexed arrays
r16 ,@(if locals
Remove cl-uglify-js
r23 `((tagbody
,@body))
Properly handle stringly-indexed arrays
r16 `((tagbody
,@body))))))
100% parser, 100% macros, 50% intrinsics, 10% api, 0% misc
r1
(ps:defpsmacro str (&rest forms)
(cond ((zerop (length forms))
"")
((and (= 1 (length forms))
(stringp (first forms)))
(first forms))
(t
`(& ,@forms))))
;;; 1loc
(ps:defpsmacro location ((name) &body body)
Menu, game saving
r11 `(setf (root locs ,name)
Properly handle stringly-indexed arrays
r16 (lambda (args)
(label-block ()
(api-call init-args args)
,@body
(api-call get-result)))))
100% parser, 100% macros, 50% intrinsics, 10% api, 0% misc
r1
(ps:defpsmacro goto (target &rest args)
`(progn
Properly handle stringly-indexed arrays
r16 (funcall (root lib goto) ,target ,args)
100% parser, 100% macros, 50% intrinsics, 10% api, 0% misc
r1 (exit)))
(ps:defpsmacro xgoto (target &rest args)
`(progn
Properly handle stringly-indexed arrays
r16 (funcall (root lib xgoto) ,target ,args)
100% parser, 100% macros, 50% intrinsics, 10% api, 0% misc
r1 (exit)))
(ps:defpsmacro desc (target)
Tutorial game works!
r6 (declare (ignore target))
100% parser, 100% macros, 50% intrinsics, 10% api, 0% misc
r1 (report-error "DESC is not supported"))
;;; 2var
Properly handle stringly-indexed arrays
r16 (ps:defpsmacro var (name index slot)
`(api-call get-var ,(string name) ,index ,slot))
100% parser, 100% macros, 50% intrinsics, 10% api, 0% misc
r1
Properly handle stringly-indexed arrays
r16 (ps:defpsmacro set ((var vname vindex vslot) value)
100% parser, 100% macros, 50% intrinsics, 10% api, 0% misc
r1 (assert (eq var 'var))
Properly handle stringly-indexed arrays
r16 `(api-call set-var ,(string vname) ,vindex ,vslot ,value))
100% parser, 100% macros, 50% intrinsics, 10% api, 0% misc
r1
;;; 3expr
(ps:defpsmacro <> (op1 op2)
`(not (equal ,op1 ,op2)))
(ps:defpsmacro ! (op1 op2)
`(not (equal ,op1 ,op2)))
;;; 4code
(ps:defpsmacro exec (&body body)
(format nil "javascript: ~{~A~^~%~}" (mapcar #'ps:ps* body)))
;;; 5arrays
;;; 6str
(ps:defpsmacro & (&rest args)
`(ps:chain "" (concat ,@args)))
;;; 7if
(ps:defpsmacro qspcond (&rest clauses)
`(cond ,@(loop :for clause :in clauses
:collect (list (first clause)
Properly handle stringly-indexed arrays
r16 `(tagbody
,@(rest clause))))))
100% parser, 100% macros, 50% intrinsics, 10% api, 0% misc
r1
;;; 8sub
;;; 9loops
;;; Yep, that's a huge kludge since Javascript doesn't support arbitrary labels
(ps:defpsmacro jump (target)
`(return-from ,(intern (string-upcase (second target)))
(funcall (ps:getprop __labels ,target))))
(ps:defpsmacro tagbody (&body body)
(let ((funcs (list nil :__nil)))
(dolist (form body)
(cond ((keywordp form)
(setf (first funcs) (reverse (first funcs)))
(push form funcs)
(push nil funcs))
(t
(push form (first funcs)))))
(setf (first funcs) (reverse (first funcs)))
(setf funcs (reverse funcs))
(if (= 2 (length funcs))
`(progn
,@body)
`(progn
(setf ,@(loop :for f :on funcs :by #'cddr
Properly handle stringly-indexed arrays
r16 :append `((ps:@ __labels ,(first f))
(block ,(intern (string-upcase (string (first f))))
,@(second f)
,@(when (third f)
`((funcall
(ps:getprop __labels ,(third f)))))))))
100% parser, 100% macros, 50% intrinsics, 10% api, 0% misc
r1 (jump (str "__nil"))))))
;;; 10dynamic
(ps:defpsmacro qspblock (&body body)
Properly handle stringly-indexed arrays
r16 `(lambda (args)
(label-block ()
(api-call init-args args)
,@body
(api-call get-result))))
100% parser, 100% macros, 50% intrinsics, 10% api, 0% misc
r1
;;; 11main
Tutorial game works!
r6 (ps:defpsmacro act (name img &body body)
`(api-call add-act ,name ,img
(lambda ()
Properly handle stringly-indexed arrays
r16 (label-block ()
Tutorial game works!
r6 ,@body))))
100% parser, 100% macros, 50% intrinsics, 10% api, 0% misc
r1
;;; 12aux
;;; 13diag
;;; 14act
;;; 15objs
;;; 16menu
;;; 17sound
;;; 18img
;;; 19input
;;; 20time
Locals
r14
;;; 21local
FOR loop
r17
;;; 22for
(ps:defpsmacro qspfor (var from to step &body body)
API call for FOR loop to make the main code less cluttered
r19 `(api-call qspfor
,(string (second var)) ,(third var) ;; name and index
,from ,to ,step
(lambda ()
(block nil
,@body
t))))