##// END OF EJS Templates
txt->qsps, remove FOR and IMG, broken LOCAL and LOOP
txt->qsps, remove FOR and IMG, broken LOCAL and LOOP

File last commit:

r60:517f9c14 default
r60:517f9c14 default
Show More
parser.lisp
664 lines | 20.6 KiB | text/x-common-lisp | CommonLispLexer
(in-package txt2web)
;;;; Parses TXT source to an intermediate representation
(eval-when (:compile-toplevel :load-toplevel :execute)
(defparameter *max-args* 10))
;;; Utility
(defun remove-nth (list nth)
(append (subseq list 0 nth)
(subseq list (1+ nth))))
(defun not-quote (char)
(not (eql #\' char)))
(defun not-doublequote (char)
(not (eql #\" char)))
(defun not-brace (char)
(not (eql #\} char)))
(defun not-integer (string)
(when (find-if-not #'digit-char-p string)
t))
(defun not-newline (char)
(not (eql #\newline char)))
(defun id-any-char (char)
(and
(not (digit-char-p char))
(not (eql #\newline char))
(not (find char " !:&=<>+-*/,'\"()[]{}"))))
(defun intern-first (list)
(list* (intern (string-upcase (first list)) "TXT2WEB.LIB")
(rest list)))
(eval-when (:compile-toplevel :load-toplevel :execute)
(defun remove-nil (list)
(remove nil list)))
(defun binop-rest (list)
(destructuring-bind (ws1 operator ws2 operand2)
list
(declare (ignore ws1 ws2))
(list (intern (string-upcase operator) "TXT2WEB.LIB") operand2)))
(defun do-binop% (left-op other-ops)
(if (null other-ops)
left-op
(destructuring-bind ((operator right-op) &rest rest-ops)
other-ops
(if (and (listp left-op)
(eq (first left-op)
operator))
(do-binop% (append left-op (list right-op)) rest-ops)
(do-binop% (list operator left-op right-op) rest-ops)))))
(walker:deftransform parser-qspmod mod (&rest args)
(list* 'qspmod (mapcar #'walker:walk-continue args)))
(defun do-binop (list)
(walker:walk 'parser-qspmod
(destructuring-bind (left-op rest-ops)
list
(do-binop% left-op
(mapcar #'binop-rest rest-ops)))))
(defun maybe-text (list)
"Leaves lists in place and applies esrap:text to everything else"
(let ((parts nil)
(part (list 'text)))
(loop :for token :in list
:do (cond ((listp token)
(push (nreverse part) parts)
(setf part (list 'text))
(push token parts))
(t (push token part))))
(push (nreverse part) parts)
(remove ""
(loop :for part :in (nreverse parts)
:collect (case (first part)
('text (p:text (rest part)))
(t part)))
:test #'equal)))
(p:defrule line-continuation (and #\_ #\newline)
(:constant nil))
(p:defrule text-spaces (+ (or #\space #\tab line-continuation))
(:text t))
(p:defrule spaces (+ (or #\space #\tab line-continuation))
(:constant nil)
(:error-report nil))
(p:defrule spaces? (* (or #\space #\tab line-continuation))
(:constant nil)
(:error-report nil))
(p:defrule colon #\:
(:constant nil))
(p:defrule equal #\=
(:constant nil))
(p:defrule alphanumeric (alphanumericp character))
(p:defrule not-newline (not-newline character))
(p:defrule squote-esc "''"
(:lambda (list)
(p:text (elt list 0))))
(p:defrule dquote-esc "\"\""
(:lambda (list)
(p:text (elt list 0))))
(p:defrule sstring-char (or squote-esc (not-quote character))
(:text t))
(p:defrule dstring-char (or dquote-esc (not-doublequote character))
(:text t))
;;; Identifiers
(defparameter *keywords* '(act addlib addobj addqst and arrcomp arrpos arrsize cla clear *clear close clr *clr cls cmdclear cmdclr copyarr countobj curact curacts curloc debug delact dellib delobj desc disablescroll disablesubex dynamic dyneval else elseif end exit loop freelib func getobj gosub goto gs gt if iif img *img inclib input instr isnum isplay jump killall killobj killqst killvar lcase len let loc local maintxt max menu mid min mod msecscount msg nl *nl no nosave obj opengame openqst or p *p pl *pl play qspver rand refint replace rgb rnd savegame selact selobj set settimer showacts showinput showobjs showstat stattxt step str strcomp strfind strpos to trim ucase unsel unselect user_text usrtxt val view wait while xgoto xgt))
(defun trim-$ (str)
(if (char= #\$ (elt str 0))
(subseq str 1)
str))
(defun qsp-keyword-p (id)
(member (intern (trim-$ (string-upcase id))) *keywords*))
(defun not-qsp-keyword-p (id)
(not (member (intern (trim-$ (string-upcase id))) *keywords*)))
(p:defrule qsp-keyword (qsp-keyword-p identifier-raw))
(p:defrule id-first (id-any-char character))
(p:defrule id-next (or (id-any-char character)
(digit-char-p character)))
(p:defrule identifier-raw (and id-first (* id-next))
(:lambda (list)
(intern (string-upcase (p:text list)) "TXT2WEB.LIB")))
(p:defrule identifier (not-qsp-keyword-p identifier-raw))
;;; Strings
(p:defrule qsp-string (or normal-string brace-string))
(p:defrule brace-string (and #\{ before-statement block-body #\})
(:lambda (list)
(list* 'lib:qspblock (third list))))
(p:defrule normal-string (or sstring dstring)
(:lambda (str)
(list* 'lib:str (or str (list "")))))
(p:defrule sstring (and #\' (* (or sstring-interpol
sstring-exec
sstring-char))
#\')
(:lambda (list)
(maybe-text (second list))))
(p:defrule dstring (and #\" (* (or dstring-interpol
dstring-exec
dstring-char))
#\")
(:lambda (list)
(maybe-text (second list))))
(defun parse-interpol (list)
(p:parse 'expression (p:text (mapcar 'second (second list)))))
(defun parse-exec (list)
(list* 'lib:exec (p:parse 'exec-body (p:text (second list)))))
(p:defrule sstring-interpol (and "<<" (+ (and (p:! ">>")
sstring-char))
">>")
(:function parse-interpol))
(p:defrule dstring-interpol (and "<<" (+ (and (p:! ">>")
dstring-char))
">>")
(:function parse-interpol))
(p:defrule sstring-exec (or (and (p:~ "\"exec:")
(+ (and (p:& (not-doublequote character)) sstring-char))
#\")
(and (p:~ "''exec:")
(+ (not-quote character))
"''"))
(:function parse-exec))
(p:defrule dstring-exec (or (and (p:~ "'exec:")
(+ (and (p:& (not-quote character)) dstring-char))
#\')
(and (p:~ "\"\"exec")
(+ (not-doublequote character))
"\"\""))
(:function parse-exec))
;;; Location
(p:defrule txt2web-grammar (and (* (or spaces #\newline))
(* location))
(:lambda (list)
`(lib:game ,@(second list))))
(p:defrule location (and location-header block-body location-end)
(:destructure (header body end)
(declare (ignore end))
`(lib:location (,header) ,@body)))
(p:defrule location-header (and #\#
(+ not-newline)
(and #\newline spaces? before-statement))
(:destructure (spaces1 name spaces2)
(declare (ignore spaces1 spaces2))
(string-upcase (string-trim " " (p:text name)))))
(p:defrule location-end (and #\- (* not-newline) #\newline before-statement)
(:constant nil))
;;; Block body
(p:defrule newline-block-body (and #\newline spaces? block-body)
(:function third))
(p:defrule block-body (* statement)
(:function remove-nil))
;; Just for <a href="exec:...'>
;; Explicitly called from that rule's production
(p:defrule exec-body (and before-statement line-body)
(:function second))
(p:defrule line-body (and inline-statement (* next-inline-statement))
(:lambda (list)
(list* (first list) (second list))))
(p:defrule before-statement (* (or #\newline spaces))
(:constant nil))
(p:defrule statement-end (or statement-end-real statement-end-block-close))
(p:defrule statement-end-real (and (or #\newline
(and #\& spaces? (p:& statement%)))
before-statement)
(:constant nil))
(p:defrule statement-end-block-close (or (p:& #\}))
(:constant nil))
(p:defrule inline-statement (and statement% spaces?)
(:function first))
(p:defrule next-inline-statement (and #\& spaces? inline-statement)
(:function third))
(p:defrule not-a-non-statement (and (p:! (p:~ "elseif"))
(p:! (p:~ "else"))
(p:! (p:~ "end"))))
(p:defrule statement (and inline-statement statement-end)
(:function first))
(p:defrule statement% (and not-a-non-statement
(or label comment string-output
block non-returning-intrinsic local
assignment expression-output))
(:function second))
(p:defrule expr-stopper (or comment block non-returning-intrinsic))
(p:defrule string-output qsp-string
(:lambda (string)
(list 'lib:main-pl string)))
(p:defrule expression-output expression
(:lambda (list)
(list 'lib:main-pl list)))
(p:defrule label (and colon identifier)
(:lambda (list)
(intern (string (second list)) :keyword)))
(p:defrule comment (and #\! (* (or qsp-string brace-comment text-spaces not-newline)))
(:constant nil))
(p:defrule brace-comment (and #\{ (* (not-brace character)) #\})
(:constant nil))
(p:defrule local (and (p:~ "local") spaces variable (p:? (and spaces? #\= spaces? expression)))
(:lambda (list)
(list* 'lib:local (third list)
(when (fourth list)
(list (fourth (fourth list)))))))
;;; Blocks
(p:defrule block (or block-act block-if block-loop))
(p:defrule block-if (and block-if-head block-if-body)
(:destructure (head body)
`(lib:qspcond (,@head ,@(first body))
,@(rest body))))
(p:defrule block-if-head (and (p:~ "if") spaces expression spaces? colon spaces?)
(:function remove-nil)
(:function cdr))
(p:defrule block-if-body (or block-if-ml block-if-sl)
(:destructure (if-body elseifs else &rest ws)
(declare (ignore ws))
`(,(remove-nil if-body) ,@elseifs ,@(when else `((else ,@else))))))
(p:defrule block-if-sl (and line-body
(p:? block-if-elseif-inline)
(p:? block-if-else-inline)
spaces?))
(p:defrule block-if-ml (and (and #\newline spaces?)
block-body
(p:? block-if-elseif)
(p:? block-if-else)
block-if-end)
(:lambda (list)
(cdr list)))
(p:defrule block-if-elseif-inline (and block-if-elseif-head line-body (p:? block-if-elseif-inline))
(:destructure (head statements elseif)
`((,@(rest head) ,@(remove-nil statements)) ,@elseif)))
(p:defrule block-if-elseif (and block-if-elseif-head statement-end block-body (p:? block-if-elseif))
(:destructure (head ws statements elseif)
(declare (ignore ws))
`((,@(rest head) ,@(remove-nil statements)) ,@elseif)))
(p:defrule block-if-elseif-head (and (p:~ "elseif") spaces expression spaces? colon spaces?)
(:function remove-nil)
(:function intern-first))
(p:defrule block-if-else-inline (and block-if-else-head line-body)
(:function second))
(p:defrule block-if-else (and block-if-else-head #\newline spaces? block-body)
(:function fourth))
(p:defrule block-if-else-head (and (p:~ "else") spaces?)
(:constant nil))
(p:defrule block-if-end (and (p:~ "end")
(p:? (and spaces (p:~ "if"))))
(:constant nil))
(p:defrule block-act (and block-act-head (or block-ml block-sl))
(:lambda (list)
(apply #'append list)))
(p:defrule block-act-head (and (p:~ "act") spaces? qsp-string spaces?
(p:? block-act-head-img)
colon spaces?)
(:lambda (list)
(intern-first (list (first list)
(third list)
(or (fifth list) '(lib:str ""))))))
(p:defrule block-act-head-img (and #\, spaces? qsp-string spaces?)
(:lambda (list)
(or (third list) "")))
(p:defrule block-loop (and block-loop-head (or block-ml block-sl))
(:lambda (list)
(apply #'append list)))
(p:defrule block-loop-head (and (p:~ "loop") spaces
(p:? (and block-loop-head-init spaces?))
block-loop-head-while spaces?
(p:? (and block-loop-head-step spaces?))
colon spaces?)
(:lambda (list)
(break "~S" list)
(list 'lib:qsploop
(elt list 2)
(elt list 6)
(elt list 9)
(elt list 10))))
(p:defrule block-loop-head-init (or local plain-assignment))
(p:defrule block-loop-head-while (and (p:~ "while") eq-expr)
(:function second))
(p:defrule block-loop-head-step (and (p:~ "step") (or plain-assignment op-assignment))
(:function second))
(p:defrule block-sl line-body)
(p:defrule block-ml (and newline-block-body block-end)
(:lambda (list)
(apply #'list* (butlast list))))
(p:defrule block-end (and (p:~ "end"))
(:constant nil))
;;; Calls
(p:defrule first-argument (and expression spaces?)
(:function first))
(p:defrule next-argument (and "," spaces? expression)
(:function third))
(p:defrule arguments (or parenthesized-arguments plain-arguments no-arguments))
(p:defrule parenthesized-arguments (and spaces? #\( base-arguments #\))
(:function third))
(p:defrule plain-arguments (and spaces? base-arguments)
(:function second))
(p:defrule no-arguments (or (and spaces? (p:& #\newline))
(and spaces? (p:& #\&))
spaces?)
(:constant nil))
(p:defrule base-arguments (or (and first-argument (* next-argument)) spaces?)
(:lambda (list)
(if (null list)
nil
(list* (first list) (second list)))))
;;; Intrinsics
(defmacro defintrinsics ((rule-name returning-rule-name non-returning-rule-name) &body clauses)
`(progn
,@(loop :for clause :in clauses
:collect `(defintrinsic ,@clause))
(p:defrule ,returning-rule-name (or ,@(remove-nil
(mapcar (lambda (clause)
(when (second clause)
(alexandria:symbolicate
'intrinsic- (first clause))))
clauses))))
(p:defrule ,non-returning-rule-name (or ,@(remove-nil
(mapcar (lambda (clause)
(unless (second clause)
(alexandria:symbolicate
'intrinsic- (first clause))))
clauses))))
(p:defrule ,rule-name (or ,returning-rule-name ,non-returning-rule-name))))
(defmacro defintrinsic (sym returning &optional (min-arity 0) max-arity &rest names)
(declare (ignore returning))
(unless max-arity
(setf max-arity *max-args*))
(setf names
(if names
(mapcar #'string-upcase names)
(list (string sym))))
`(p:defrule ,(alexandria:symbolicate 'intrinsic- sym)
(and (p:? #\$) (or ,@(loop :for name :in names :collect `(p:~ ,name)))
arguments)
(:destructure (dollar name arguments)
(declare (ignore dollar))
(unless (<= ,min-arity (length arguments) ,max-arity)
(error "Intrinsic ~A expects between ~A and ~A arguments but ~A were provided:~%~S"
name ,min-arity ,max-arity (length arguments) arguments))
(list* ',(intern (string sym) "TXT2WEB.LIB") arguments))))
(defintrinsics (intrinsic returning-intrinsic non-returning-intrinsic)
;; Transitions
(goto% nil 0 nil "gt" "goto")
(xgoto% nil 0 nil "xgt" "xgoto")
;; Variables
(killvar nil 0 2)
;; Expressions
(obj t 1 1)
(loc t 1 1)
(no t 1 1)
;; Basic
(qspver t 0 0)
(curloc t 0 0)
(rand t 1 2)
(rnd t 0 0)
(qspmax t 1 nil "max")
(qspmin t 1 nil "min")
;; Arrays
(killall nil 0 0)
(copyarr nil 2 4)
(arrsize t 1 1)
(arrpos t 2 3)
(arrcomp t 2 3)
;; Strings
(len t 1 1)
(mid t 2 3)
(ucase t 1 1)
(lcase t 1 1)
(trim t 1 1)
(qspreplace t 2 3 "replace")
(instr t 2 3)
(isnum t 1 1)
(val t 1 1)
(qspstr t 1 1 "str")
(strcomp t 2 2)
(strfind t 2 3)
(strpos t 2 3)
;; IF
(iif t 2 3)
;; Subs
(gosub nil 1 nil "gosub" "gs")
(func t 1 nil)
(exit nil 0 0)
;; Jump
(jump nil 1 1)
;; Dynamic
(dynamic nil 1 nil)
(dyneval t 1 nil)
;; Sound
(play nil 1 2)
(isplay t 1 1)
(close nil 1 1)
(closeall nil 0 0 "close all")
;; Main window
(main-pl nil 1 1 "*pl")
(main-nl nil 0 1 "*nl")
(main-p nil 1 1 "*p")
(maintxt t 0 0)
(desc t 1 1)
(main-clear nil 0 0 "*clear" "*clr")
;; Aux window
(showstat nil 1 1)
(stat-pl nil 1 1 "pl")
(stat-nl nil 0 1 "nl")
(stat-p nil 1 1 "p")
(stattxt t 0 0)
(stat-clear nil 0 0 "clear" "clr")
(cls nil 0 0)
;; Dialog
(msg nil 1 1)
;; Acts
(showacts nil 1 1)
(delact nil 1 1 "delact" "del act")
(curacts t 0 0)
(selact t 0 0)
(cla nil 0 0)
;; Objects
(showobjs nil 1 1)
(addobj nil 1 3 "addobj" "add obj")
(delobj nil 1 1 "delobj" "del obj")
(killobj nil 0 1)
(countobj t 0 0)
(getobj t 1 1)
(selobj t 0 0)
(unsel nil 0 0 "unsel" "unselect")
;; Menu
(menu nil 1 1)
;; Images
(refint nil 0 0)
(view nil 0 1)
(img nil 1)
(*img nil 1)
;; Fonts
(rgb t 3 3)
;; Input
(showinput nil 1 1)
(usertxt t 0 0 "user_text" "usrtxt")
(cmdclear nil 0 0 "cmdclear" "cmdclr")
(input t 1 1)
;; Files
(openqst nil 1 1)
(addqst nil 1 1 "addqst" "addlib" "inclib")
(killqst nil 1 1 "killqst" "dellib" "freelib")
(opengame nil 0 0)
(savegame nil 0 0)
;; Real time
(wait nil 1 1)
(msecscount t 0 0)
(settimer nil 1 1))
;;; Expression
(p:defrule expression or-expr)
(p:defrule or-expr (and and-expr (* (and spaces? or-op spaces? and-expr)))
(:function do-binop))
(p:defrule and-expr (and eq-expr (* (and spaces? and-op spaces? eq-expr)))
(:function do-binop))
(p:defrule eq-expr (and sum-expr (* (and spaces? (or "<=" ">=" "=<" "=>" "<>"
"=" "<" ">" "!")
spaces? sum-expr)))
(:function do-binop))
(p:defrule sum-expr (and mod-expr (* (and spaces? (or #\+ #\-) spaces? mod-expr)))
(:function do-binop))
(p:defrule mod-expr (and mul-expr (* (and spaces? (p:~ "mod") spaces? mul-expr)))
(:function do-binop))
(p:defrule mul-expr (and unary-expr (* (and spaces? (or #\* #\/) spaces? unary-expr)))
(:function do-binop))
(p:defrule unary-expr (and (p:? (or #\+ #\-)) atom-expr)
(:lambda (list)
(let ((expr (remove-nil list)))
(if (= 1 (length expr))
(first expr)
(intern-first expr)))))
(p:defrule atom-expr (and (or variable literal returning-intrinsic paren-expr) spaces?)
(:function first))
(p:defrule paren-expr (and #\( spaces? expression spaces? #\))
(:function third))
(p:defrule or-op (p:~ "or")
(:constant "or"))
(p:defrule and-op (p:~ "and")
(:constant "and"))
;;; Variables
(p:defrule variable (and identifier (p:? array-index))
(:destructure (id idx-raw)
(let ((idx (case idx-raw
((nil) 0)
(:last nil)
(t idx-raw))))
(list 'lib:qspvar id idx))))
(p:defrule array-index (and #\[ spaces? (p:? expression) spaces? #\])
(:lambda (list)
(or (third list) :last)))
(p:defrule assignment (or kw-assignment plain-assignment op-assignment)
(:destructure (qspvar eq expr)
(declare (ignore eq))
(list 'lib:set qspvar expr)))
(p:defrule kw-assignment (and (or (p:~ "let") (p:~ "set")) spaces? (or op-assignment plain-assignment))
(:function third))
(p:defrule op-assignment (and variable spaces? (or "+" "-" "*" "/") #\= spaces? expression)
(:destructure (qspvar ws1 op eq ws2 expr)
(declare (ignore ws1 ws2))
(list qspvar eq (intern-first (list op qspvar expr)))))
(p:defrule plain-assignment (and variable spaces? #\= spaces? expression)
(:function remove-nil))
;;; Non-string literals
(p:defrule literal (or qsp-string brace-string number))
(p:defrule number (+ (or #\0 #\1 #\2 #\3 #\4 #\5 #\6 #\7 #\8 #\9))
(:lambda (list)
(parse-integer (p:text list))))