;;; Copyright (c) 1998--2004 ;;; John Carroll, Ann Copestake, Robert Malouf, Stephan Oepen; ;;; see `LICENSE' for conditions. ;;; WARNING: the variable-generation function and some structures are ;;; duplicated in rmrs/standalone.lisp (in-package "MRS") ;;; Reorganised MRS code - ;;; this is the basic MRS file, which defines the lisp structures ;;; used for internally encoding MRS. ;;; ideally handle and liszt should be renamed, but life's too short (defstruct (basemrs) top-h liszt h-cons a-cons icons vcs) ;;; a-cons added to allow for constraints on attachment ;;; i-cons - information structure and anaphora ;;; rmrs is a substructure of this (see basermrs.lisp) (defstruct (psoa (:include basemrs)) index) ;;; psoa records an index - this really is the equivalent of the semstruct ;;; in RMRS - the two should possibly be amalgamated and index should be ;;; replaced by hook, when the code for displaying MRSs according to the ;;; algebra is finally written ;;; for the algebra - rationalise this later ;;; not just psoa but rmrs semstruct in comp.lisp (defstruct (sement (:include basemrs)) hook slots equalities) (defstruct (hook) index ltop xarg anchor) (defstruct (slot) hook name) ;;; I have changed the old `sort' to `pred' - the old name was ;;; seriously confusing ;;; ep removed again - was used for the `simple' RMRS ;;; but that's no longer supported (defstruct (rel-base) pred ; relation name flist) (defstruct (rel (:include rel-base)) str handel anchor ; used by RMRS in version ; without INGs parameter-strings ; the constant values ; a junk slot used by the ; generator and comparison code extra ; extra is a junk slot ; needed for the munging rules cfrom cto lnk) ; link to surface element(s) (defstruct (fvpair) feature value) ;;; feature is a symbol ;;; value is either a constant or ;;; a var structure which contains a string plus a number ;;; (unique to this MRS) (defstruct (var-base) type extra) ; e.g. agreement values (defstruct (var (:include var-base)) id) (defstruct (extrapair) feature value) (defstruct (grammar-var (:include var))) ;;; a sort of placeholder variable used in RMRS code (defstruct (hcons) relation scarg outscpd) ;;; relation is one of "qeq", "lheq" or "outscopes" as in the rmrs.dtd ;;; the code for grammar read in must convert the type to one ;;; of these. although at the moment, only qeqs are supported. (defstruct (icons) relation iarg1 iarg2) ;;; iargs must be `normal' variables ;;; The following structures are for attachment constraints as used ;;; by Berthold. ;;; The phrase to be attached supplies a pair of index and label, ;;; and the target is a set of such pairs. ;;; These are stored on a-cons (defstruct (disj-cons) index-lbl target) (defstruct (index-lbl) index lbl) ;;; In an attempt to clean up a messy situation, ;;; var-types are now all lower-case strings. ;;; Although I wouldn't generally use strings ;;; to represent enumerated values, it saves ;;; considerable messing around to do so, which ;;; seems more important than the minor efficiency ;;; hit. In effect, the inventory of var-types is ;;; part of the SEM-I. For now we have the ;;; following (from the RMRS DTD) ;;; (x|e|h|u|l) ;;; the mapping from the ERG (in mrsoutput.lisp) ;;; adds d and v (should be u??) (defun var-string (var) (cond ((grammar-var-p var) (var-id var)) ((and (var-p var) (not (eq (var-id var) :dummy))) (format nil "~(~A~)~@[~A~]" (or (var-type var) "u") (var-id var))) ((var-base-p var) (format nil "~@[~(~A~)~]" (or (var-base-type var) "u"))) (t (error "var expected ~A found" var)))) ;;; macros moved from mrsresolve (defmacro is-handel-var (var) ;;; test is whether the type is "h" `(and (var-p ,var) (equal (var-type ,var) "h"))) (defmacro nonquantified-var-p (var) ;;; true if the type is anything other than x `(and (var-p ,var) (not (equal (var-type ,var) "x")))) (defun is-top-semantics-type (pred) (eq pred *top-semantics-type*)) ;;; variable generator - moved from mrsoutput because it could ;;; potentially be called without that code having been read in (defvar *variable-generator* nil) (defun create-variable-generator (&optional start) (let ((number (or start 0))) #'(lambda nil (incf number) number))) (defun init-variable-generator () (setf *variable-generator* (create-variable-generator))) (init-variable-generator) ;;; test for variable equality (defun eql-var-id (var1 var2) ;;; can't be macroized cos used where fn is required ;;; has to be `equal' since ;;; used for grammar vars etc in RMRS composition code ;;; where the id is a string (equal (var-id var1) (var-id var2))) ;;; ;;; make debugging with MRSs a little easier: print very compact representation ;;; of object by default; set *mrs-raw-output-p* to see things in full glory. ;;; (defparameter *mrs-raw-output-p* nil) ;;; ;;; provide a way of suppressing select roles in output; useful when preparing ;;; the input to UTool, e.g. for classification or solving, so as to omit the ;;; pesky TPC and PSV pseudo-roles. (5-jul-06; oe) ;;; (defparameter *output-ignored-roles* nil) (defmethod print-object ((object psoa) stream) (if *mrs-raw-output-p* (call-next-method) (output-mrs1 object 'terse stream))) (defmethod print-object ((object rel) stream) (if *mrs-raw-output-p* (call-next-method) (let ((pred (rel-pred object)) (lnk (output-lnk (rel-lnk object) :stream nil)) (roles (rel-flist object))) (format stream "~@[~a:~]~(~a~)~@[~a~](" (and (rel-handel object) (var-string (rel-handel object))) (if (stringp pred) (format nil "~s" pred) (or pred "_")) lnk) (loop for role in roles for value = (fvpair-value role) do (format stream "~:[ ~;~]~a" (eq role (first roles)) value)) (format stream ")")))) (defmethod print-object ((object var) stream) (if *mrs-raw-output-p* (call-next-method) (format stream "~a" (var-string object)))) ;;; The MRS structure could be output either as simple ascii ;;; or as LaTeX and possibly in other ways ;;; So use the same trick as the LKB to avoid unnecessary work ;;; for different output types (defparameter *mrs-display-structure* nil) (defun def-print-operations (class indentation stream) (setf *mrs-display-structure* (make-instance class :indentation indentation :stream stream))) ;;; Sept 04 - now using indentation more systematically, ;;; allows for two column output for comparisons ;;; ;;; Generic output-type class ;;; (defclass output-type () ((indentation :initform 0 :initarg :indentation) (stream :initform t :initarg :stream))) (defmethod initialize-display-structure ((class output-type) mrs &optional id) (declare (ignore mrs id))) (defmethod mrs-output-error-fn ((mrsout output-type) mrs-instance) (with-slots (stream) mrsout (format stream "~%::: ~A is not a psoa struct~%" mrs-instance))) (defmethod mrs-output-max-width-fn ((mrsout output-type)) nil) (defmethod mrs-output-end-fvpair-fn ((mrsout output-type)) nil) ;;; generic null method here so no crashes because some ;;; outputs don't allow for icons yet (defmethod mrs-output-start-icons ((mrsout output-type)) nil) (defmethod mrs-output-icons ((mrsout output-type) reln higher lower first-p higher-id higher-sort lower-id lower-sort) (declare (ignore reln higher lower first-p higher-id higher-sort lower-id lower-sort)) nil) (defmethod mrs-output-end-icons ((mrsout output-type)) nil) (defmethod mrs-output-start-a-cons ((mrsout output-type)) nil) (defmethod mrs-output-disj-cons-spec ((mrsout output-type) first-p) (declare (ignore first-p)) nil) (defmethod mrs-output-disj-cons-start-target ((mrsout output-type)) nil) (defmethod mrs-output-disj-cons-end-target ((mrsout output-type)) nil) (defmethod mrs-output-end-a-cons ((mrsout output-type)) nil) (defmethod mrs-output-ilp ((mrsout output-type) var1 var2 first-p) (declare (ignore var1 var2 first-p)) nil) (defmethod mrs-output-vcs ((mrsout output-type) vcs) (declare (ignore vcs)) nil) ;;; ;;; simple output-type class ;;; (defclass simple (output-type) ((line-per-rel :initform nil :initarg line-per-rel))) (defmethod mrs-output-start-fn ((mrsout simple)) (with-slots (stream) mrsout ;; initial space otherwise bounding box could be incorrect ;; _fix_me_ this is a dramatic change (e.g. in Redwoods export files) (format stream #+:logon "~V%" #-:logon " ~V%" 1))) (defmethod mrs-output-end-fn ((mrsout simple)) (with-slots (stream) mrsout (format stream "~V%" 1))) (defmethod mrs-output-start-psoa ((mrsout simple)) (with-slots (stream indentation) mrsout (format stream "~VT[" indentation))) (defmethod mrs-output-top-h ((mrsout simple) handel-val &optional properties type id) (declare (ignore properties type id)) (when (and handel-val *rel-handel-path*) (with-slots (stream) mrsout (format stream " TOP: ~(~a~)" handel-val)))) (defmethod mrs-output-index ((mrsout simple) index-val &optional properties type id) (declare (ignore properties type id)) (with-slots (stream indentation) mrsout (when index-val (format stream "~%~VT INDEX: ~(~a~)" indentation index-val)))) (defmethod mrs-output-start-liszt ((mrsout simple)) (with-slots (stream indentation) mrsout (format stream "~%~VT RELS: <" indentation) (setf indentation (+ indentation 10)))) (defmethod mrs-output-var-fn ((mrsout simple) var-string &optional properties type id) (declare (ignore properties type id)) (with-slots (stream) mrsout (format stream "~(~a~)" var-string))) (defmethod mrs-output-atomic-fn ((mrsout simple) atomic-value) (with-slots (stream) mrsout (format stream "~S" atomic-value))) (defmethod mrs-output-start-rel ((mrsout simple) pred first-p class &optional lnk str) (declare (ignore first-p class str)) (with-slots (stream indentation) mrsout (format stream "~%") ;; ;; decide which predicates to output as quoted strings, vs. as what looks ;; like an unquoted symbol (but actually not using lisp symbol syntax) ;; (if (or (and (null *normalize-predicates-p*) (stringp pred)) (when *normalize-predicates-p* (loop for c across pred thereis (or (member c '(#\" #\< #\[) :test #'char=) (whitespacep c))))) (format stream "~VT[ ~s" indentation pred) (format stream "~VT[ ~(~a~)" indentation (or pred "_"))) (output-lnk lnk :stream stream))) (defmethod mrs-output-rel-handel ((mrsout simple) handel &optional properties sort id) (declare (ignore properties sort id)) (if handel (with-slots (stream indentation) mrsout (format stream "~%~VT~A: ~(~a~)" (+ indentation 2) 'lbl handel)))) (defmethod mrs-output-label-fn ((mrsout simple) label) (with-slots (stream indentation line-per-rel) mrsout (if line-per-rel (format stream " ~a: " (+ indentation 2) label) (format stream "~%~VT~a: " (+ indentation 2) label)))) (defmethod mrs-output-start-extra ((mrsout simple) var-type) (with-slots (stream indentation) mrsout (format stream " [ ~A" var-type))) (defmethod mrs-output-extra-feat ((mrsout simple) feat) (with-slots (stream indentation) mrsout (format stream " ~A: " feat))) (defmethod mrs-output-extra-val ((mrsout simple) val) (with-slots (stream) mrsout (format stream "~A" val))) (defmethod mrs-output-end-extra ((mrsout simple)) (with-slots (stream) mrsout (format stream " ]"))) (defmethod mrs-output-end-rel ((mrsout simple)) (with-slots (stream) mrsout (format stream " ]"))) (defmethod mrs-output-end-liszt ((mrsout simple)) (with-slots (stream indentation) mrsout (format stream " >") (setf indentation (- indentation 10)))) (defmethod mrs-output-start-h-cons ((mrsout simple)) (with-slots (stream indentation) mrsout (format stream "~%~VT HCONS: <" indentation))) (defmethod mrs-output-outscopes ((mrsout simple) reln higher lower first-p higher-id higher-sort lower-id lower-sort) (declare (ignore first-p higher-id higher-sort lower-id lower-sort)) (with-slots (stream indentation) mrsout (format stream " ~(~a~) ~A ~(~a~)" higher reln lower))) (defmethod mrs-output-end-h-cons ((mrsout simple)) (with-slots (stream) mrsout (format stream " >"))) (defmethod mrs-output-start-icons ((mrsout simple)) (with-slots (stream indentation) mrsout (format stream "~%~VT ICONS: <" indentation))) (defmethod mrs-output-icons ((mrsout simple) reln higher lower first-p higher-id higher-sort lower-id lower-sort) (declare (ignore first-p higher-id higher-sort lower-id lower-sort)) (with-slots (stream indentation) mrsout (format stream " ~(~a~) ~A ~(~a~)" higher reln lower))) (defmethod mrs-output-end-icons ((mrsout simple)) (with-slots (stream) mrsout (format stream " >"))) #| output is e.g., ACONS: in <,>, in <,> |# (defmethod mrs-output-start-a-cons ((mrsout simple)) (with-slots (stream indentation) mrsout (format stream "~%~VT ACONS: " indentation))) (defmethod mrs-output-disj-cons-spec ((mrsout simple) first-acons) (with-slots (stream indentation) mrsout (format stream "~A " (if first-acons "" ",") indentation))) (defmethod mrs-output-disj-cons-start-target ((mrsout simple)) (with-slots (stream indentation) mrsout (format stream " in <" indentation))) (defmethod mrs-output-disj-cons-end-target ((mrsout simple)) (with-slots (stream indentation) mrsout (format stream ">" indentation))) (defmethod mrs-output-ilp ((mrsout simple) var1 var2 position) ;;; position can be :spec, :first-target or :target (with-slots (stream indentation) mrsout (format stream "~A<~A,~A>" (if (eql position :target) "," "") var1 var2))) (defmethod mrs-output-end-a-cons ((mrsout simple)) (with-slots (stream) mrsout (format stream ""))) (defmethod mrs-output-vcs ((mrs simple) vcs) (with-slots (stream indentation) mrs (format stream "~%~vt VCS: < " indentation) (loop for foo in vcs do (format stream "~(~a~) " foo)) (format stream ">"))) (defmethod mrs-output-end-psoa ((mrsout simple)) (with-slots (stream indentation) mrsout (format stream " ]~%" indentation))) ;;; ;;; active output class (for on-line browsing in CLIM) ;;; (defclass active-t (simple) ()) (defmethod mrs-output-start-rel ((mrsout active-t) pred first-p class &optional lnk str) (declare (ignore first-p class str)) (with-slots (stream indentation) mrsout (format stream "~%") (format stream "~VT[ " indentation) (lkb::add-mrs-pred-region stream pred *normalize-predicates-p*) (output-lnk lnk :stream stream))) ;;; ;;; column-two output class (for displaying two MRSs side by side) ;;; (defclass column-two (active-t) ()) (defmethod mrs-output-start-fn ((mrsout column-two)) (with-slots (stream indentation) mrsout (setf indentation (+ indentation 60)) (format stream " ~V%" 1))) ;;; ;;; indexed output-type class ;;; (defclass indexed (output-type) ((need-comma :initform nil) (temp-pred :initform nil))) (defmethod mrs-output-start-fn ((mrsout indexed)) (with-slots (stream) mrsout (format stream " ~V%" 1))) (defmethod mrs-output-end-fn ((mrsout indexed)) (with-slots (stream) mrsout (format stream "~V%" 1))) (defmethod mrs-output-start-psoa ((mrsout indexed)) (with-slots (stream) mrsout (format stream "<"))) (defmethod mrs-output-top-h ((mrsout indexed) handel-val &optional properties type id) (declare (ignore properties type id)) (if handel-val (with-slots (stream) mrsout (format stream "~(~a~)," handel-val)))) (defmethod mrs-output-index ((mrsout indexed) index-val &optional properties type id) (declare (ignore properties type id)) (with-slots (stream) mrsout (format stream "~(~a~)" index-val))) (defmethod mrs-output-start-liszt ((mrsout indexed)) (with-slots (stream) mrsout (format stream ",~%{"))) (defmethod mrs-output-var-fn ((mrsout indexed) var-string &optional properties type id) (declare (ignore properties type id)) (with-slots (stream) mrsout (format stream "~(~a~)" (remove-variable-junk var-string)))) (defmethod mrs-output-atomic-fn ((mrsout indexed) atomic-value) (with-slots (stream) mrsout (format stream "~S" atomic-value))) (defmethod mrs-output-start-rel ((mrsout indexed) pred first-p class &optional lnk str) (declare (ignore class str)) (with-slots (stream temp-pred) mrsout (let ((lnk (output-lnk lnk :stream nil))) (setf temp-pred (format nil "~a~a" pred lnk))) (unless first-p (format stream ",~%")))) (defmethod mrs-output-rel-handel ((mrsout indexed) handel &optional properties sort id) (declare (ignore properties sort id)) (if handel (with-slots (stream temp-pred) mrsout (format stream "~(~a~):~A(" handel (remove-right-sequence *sem-relation-suffix* (string-downcase temp-pred)))) (with-slots (stream temp-pred) mrsout (format stream "~A(" (remove-right-sequence *sem-relation-suffix* (string-downcase temp-pred)))))) (defmethod mrs-output-label-fn ((mrsout indexed) label) (declare (ignore label)) (with-slots (stream need-comma) mrsout (when need-comma (format stream ", ")) (setf need-comma t))) (defmethod mrs-output-start-extra ((mrsout indexed) var-type) (declare (ignore var-type)) nil) ; (with-slots (stream) mrsout ; (format stream ":~A" var-type))) (defmethod mrs-output-extra-feat ((mrsout indexed) feat) (declare (ignore feat)) nil) (defmethod mrs-output-extra-val ((mrsout indexed) val) (with-slots (stream) mrsout (format stream ":~A" val))) (defmethod mrs-output-end-extra ((mrsout indexed)) nil) (defmethod mrs-output-end-rel ((mrsout indexed)) (with-slots (stream need-comma) mrsout (format stream ")") (setf need-comma nil))) (defmethod mrs-output-end-liszt ((mrsout indexed)) (with-slots (stream) mrsout (format stream "},"))) (defmethod mrs-output-start-h-cons ((mrsout indexed)) (with-slots (stream) mrsout (format stream "~%{"))) ;;; ??? (defmethod mrs-output-outscopes ((mrsout indexed) reln higher lower first-p higher-id higher-sort lower-id lower-sort) (declare (ignore higher-id higher-sort lower-id lower-sort)) (with-slots (stream) mrsout (unless first-p (format stream ",~%")) (format stream "~(~a~) ~A ~(~a~)" higher reln lower))) (defmethod mrs-output-end-h-cons ((mrsout indexed)) (with-slots (stream) mrsout (format stream "}"))) (defmethod mrs-output-start-icons ((mrsout indexed)) (with-slots (stream) mrsout (format stream "~%{"))) ;;; ??? (defmethod mrs-output-icons ((mrsout indexed) reln higher lower first-p higher-id higher-sort lower-id lower-sort) (declare (ignore higher-id higher-sort lower-id lower-sort)) (with-slots (stream) mrsout (unless first-p (format stream ",~%")) (format stream "~(~a~) ~A ~(~a~)" higher reln lower))) (defmethod mrs-output-end-icons ((mrsout indexed)) (with-slots (stream) mrsout (format stream "}"))) (defmethod mrs-output-end-psoa ((mrsout indexed)) (with-slots (stream) mrsout (format stream ">~%" ))) ;;; dropping the `extra' stuff (defclass simple-indexed (indexed) ()) (defmethod mrs-output-extra-val ((mrsout simple-indexed) val) (declare (ignore val)) nil) ;;; ;;; prolog output-type class ;;; #| assume the following structure psoa(handel,index,liszt,hcons) handel is a handle-variable index is a variable liszt is a list of rels rel(relation,handel,attrvals) relation is a string handel is a handle-variable attrvals is a list of attrvals attrval(attribute,value) attribute is a string value is a string or a variable or a handle-variable hcons is a list of qeqs qeq(higher,lower) higher and lower are handle-variables |# (defclass prolog (output-type) ((need-comma :initform nil))) (defmethod mrs-output-start-fn ((mrsout prolog)) (with-slots (stream) mrsout (format stream " ~V%" 1))) (defmethod mrs-output-end-fn ((mrsout prolog)) (with-slots (stream) mrsout (format stream "~V%" 1))) (defmethod mrs-output-start-psoa ((mrsout prolog)) (with-slots (stream) mrsout (format stream "psoa("))) (defmethod mrs-output-top-h ((mrsout prolog) handel-val &optional properties type id) (declare (ignore properties type id)) (with-slots (stream) mrsout (format stream "~(~a~)" handel-val))) (defmethod mrs-output-index ((mrsout prolog) index-val &optional properties type id) (declare (ignore properties type id)) (with-slots (stream) mrsout (format stream ",~(~a~)" index-val))) (defmethod mrs-output-start-liszt ((mrsout prolog)) (with-slots (stream) mrsout (format stream ",["))) (defmethod mrs-output-var-fn ((mrsout prolog) var-string &optional properties type id) (declare (ignore properties type id)) (with-slots (stream) mrsout (format stream "~(~a~))" (remove-variable-junk var-string)))) (defmethod mrs-output-atomic-fn ((mrsout prolog) atomic-value) (with-slots (stream) mrsout (if (stringp atomic-value) (format stream "'~A')" atomic-value) (format stream "~A)" atomic-value)))) (defmethod mrs-output-start-rel ((mrsout prolog) pred first-p class &optional lnk str) (declare (ignore class lnk str)) (with-slots (stream) mrsout (unless first-p (format stream ",")) (format stream "~%rel('~A'," ; JAC: added line break (remove-right-sequence *sem-relation-suffix* (string-downcase pred))))) (defmethod mrs-output-rel-handel ((mrsout prolog) handel &optional properties sort id) (declare (ignore properties sort id)) (with-slots (stream temp-pred) mrsout (format stream "~(~a~),[" handel))) (defmethod mrs-output-label-fn ((mrsout prolog) label) (with-slots (stream need-comma) mrsout (when need-comma (format stream ",")) (setf need-comma t) (format stream "attrval('~A'," label))) (defmethod mrs-output-start-extra ((mrsout prolog) var-type) (declare (ignore var-type)) nil) (defmethod mrs-output-extra-feat ((mrsout prolog) feat) (declare (ignore feat)) nil) (defmethod mrs-output-extra-val ((mrsout prolog) val) (declare (ignore val)) nil) (defmethod mrs-output-end-extra ((mrsout prolog)) nil) (defmethod mrs-output-end-rel ((mrsout prolog)) (with-slots (stream need-comma) mrsout (setf need-comma nil) (format stream "])"))) (defmethod mrs-output-end-liszt ((mrsout prolog)) (with-slots (stream) mrsout (format stream "]"))) (defmethod mrs-output-start-h-cons ((mrsout prolog)) (with-slots (stream) mrsout (format stream ",~%hcons(["))) ; JAC: added line break (defmethod mrs-output-outscopes ((mrsout prolog) reln higher lower first-p higher-id higher-sort lower-id lower-sort) (declare (ignore higher-id higher-sort lower-id lower-sort)) (with-slots (stream) mrsout (unless first-p (format stream ",")) (format stream "~A(~(~a~),~(~a~))" (string-downcase reln) higher lower))) (defmethod mrs-output-end-h-cons ((mrsout prolog)) (with-slots (stream need-comma) mrsout (setf need-comma nil) (format stream "])"))) (defmethod mrs-output-end-psoa ((mrsout prolog)) (with-slots (stream) mrsout (format stream ")~%"))) ;;; ;;; HTML output-type class ;;; (defparameter *mrs-relations-per-row* 6) (defun mrs-variable-html (variable properties id class stream) (let ((string (make-string-output-stream))) (when (and properties (not (stringp properties))) (format string "") (loop for property in properties do (format string "" (extrapair-feature property) (extrapair-value property))) (format string "
~a~ ~(~a~)
")) (format stream "~@[~% ~]~ <~:[span~;div~] class=\"mrsVariable~a~:(~a~)\"~% ~ onMouseOver=\"mrsVariableSelect('~a~:(~a~)', '~a')\"~% ~ onMouseOut=\"mrsVariableUnselect('~a~:(~a~)')\">~(~a~)~ ~ ~:[~;~%~%~]" class class id variable id variable (if (stringp properties) properties (get-output-stream-string string)) id variable variable class class))) (defclass html (output-type) ((id :initform 0) (class :initform nil) (nrels :initform nil) (i :initform nil) (nrows :initform nil) (hconss :initform nil))) (defmethod initialize-display-structure ((class html) mrs &optional n) (with-slots (id class nrels nrows i) class (setf id n) (setf class (determine-mrs-class mrs)) (setf nrels (length (psoa-liszt mrs))) (setf nrows (ceiling nrels *mrs-relations-per-row*)) (setf i 0))) (defmethod mrs-output-start-fn ((mrs html)) (with-slots (stream) mrs (format stream "~V%" 1))) (defmethod mrs-output-end-fn ((mrs html)) (with-slots (stream) mrs (format stream "~V%" 1))) (defmethod mrs-output-start-psoa ((mrs html)) (with-slots (stream class) mrs (format stream "~%" class class))) (defmethod mrs-output-top-h ((mrs html) handle &optional properties type var-id) (declare (ignore properties type var-id)) (when (and handle *rel-handel-path*) (with-slots (id stream) mrs (format stream "~%") (mrs-variable-html handle nil id "mrsValueTop" stream)))) (defmethod mrs-output-index ((mrs html) index &optional properties type var-id) (declare (ignore type var-id)) (when index (with-slots (id stream) mrs (format stream "~%~%") (mrs-variable-html index properties id "mrsFeatureIndex" stream)))) (defmethod mrs-output-start-liszt ((mrs html)) (with-slots (stream nrows) mrs (format stream "~%~%~ ~%"))) (defmethod mrs-output-start-h-cons ((mrs html)) (with-slots (stream) mrs (format stream "~ ~%"))) (defmethod mrs-output-end-psoa ((mrs html)) (with-slots (id hconss stream) mrs (format stream "
TOP
INDEX
RELS~%~ ~%~%~ ~%~ ~% ~
{~% ~%~
~%" nrows))) (defmethod mrs-output-var-fn ((mrs html) variable &optional properties type var-id) (declare (ignore type var-id)) (with-slots (id stream) mrs (mrs-variable-html variable properties id "mrsValue" stream))) (defmethod mrs-output-atomic-fn ((mrs html) value) (with-slots (stream) mrs (format stream "~%" value))) (defmethod mrs-output-start-rel ((mrs html) pred firstp class &optional lnk str) (declare (ignore firstp str)) (with-slots (stream i nrows) mrs (when (and (not (zerop i)) (zerop (mod i *mrs-relations-per-row*))) (format stream "
~a
~%")) (let* ((pred (string-downcase pred)) (pred (remove-right-sequence *sem-relation-suffix* pred))) (format stream " ~%"))) (defmethod mrs-output-end-liszt ((mrs html)) (with-slots (stream) mrs (format stream "
~% ~ ~%") (incf i))) (defmethod mrs-output-rel-handel ((mrs html) handle &optional properties sort id) (declare (ignore properties sort id)) (when handle (with-slots (id stream) mrs (format stream " ") (mrs-variable-html handle nil id "mrsValue" stream)))) (defmethod mrs-output-label-fn ((mrs html) label) (with-slots (stream) mrs (format stream " " label))) (defmethod mrs-output-start-extra ((mrs html) type) (declare (ignore type))) (defmethod mrs-output-extra-feat ((mrs html) feature) (declare (ignore feature))) (defmethod mrs-output-extra-val ((mrs html) value) (declare (ignore value))) (defmethod mrs-output-end-extra ((mrs html))) (defmethod mrs-output-end-rel ((mrs html)) (with-slots (stream) mrs (format stream "
~(~a~)" class class pred)) (output-lnk lnk :stream stream :format :html) (format stream "
LBL
~a
~% ~
}
~%
HCONS{ "))) (defmethod mrs-output-outscopes ((mrs html) relation higher lower firstp higher-id higher-sort lower-id lower-sort) (declare (ignore higher-id higher-sort lower-id lower-sort)) (with-slots (id hconss stream) mrs (unless firstp (format stream ", ")) (format stream "~(~a~)~  ~a ~ ~(~a~)" id higher id higher id higher higher (if (string-equal (string relation) "qeq") "=q" relation) id lower id lower id lower lower) (push (cons higher lower) hconss))) (defmethod mrs-output-end-h-cons ((mrs html)) (with-slots (stream) mrs (format stream " }
") ;; ;; generate JavaScript arrays for bi-directional HCONS indexing ;; (loop initially (format stream "~%")))) ;;; ;;; JSON output, using an alternative approach: the Common Lisp pretty printing ;;; machinery, which gives us logical block structure and indentation. ;;; (defun mrs-output-json (mrs &key (stream t) (propertiesp t) (columns *print-right-margin*) prefix) (if (null stream) (with-output-to-string (stream) (mrs-output-json mrs :stream stream :propertiesp propertiesp :columns columns)) (let ((label (psoa-top-h mrs)) (index (psoa-index mrs)) (variables nil) (*print-right-margin* columns)) (when prefix (write-string prefix stream)) (pprint-logical-block (stream nil :prefix "{" :suffix "}") (when (var-p label) (format stream "\"top\": ~a, " (mrs-variable-output-json label :objectp nil)) (pprint-newline :mandatory stream) (pushnew label variables :test #'eq)) (when (var-p index) (format stream "\"index\": ~a, " (mrs-variable-output-json index :objectp nil)) (pprint-newline :mandatory stream) (pushnew index variables :test #'eq)) (format stream "\"relations\": ") (pprint-newline :mandatory stream) (pprint-logical-block (stream nil :prefix "[" :suffix "]") (loop with rels = (psoa-liszt mrs) with last = (first (last rels)) for ep in rels for label = (rel-handel ep) for predicate = (rel-pred ep) for lnk = (rel-lnk ep) do (pprint-logical-block (stream nil :prefix "{" :suffix "}") (format stream "\"label\": ~a, \"predicate\": ~s, \"lnk\": " (mrs-variable-output-json label :objectp nil) predicate) (pushnew label variables :test #'eq) (output-lnk lnk :stream stream :format :json) (format stream ", \"arguments\":") (pprint-newline :fill stream) (format stream " ") (pprint-logical-block (stream nil :prefix "{" :suffix "}") (loop with arguments = (rel-flist ep) with last = (first (last arguments)) for argument in arguments for role = (fvpair-feature argument) for value = (fvpair-value argument) do (format stream "~s: ~a" (string-upcase role) (cond ((var-p value) (pushnew value variables :test #'eq) (mrs-variable-output-json value :objectp nil)) (t (format nil "~s" (string value))))) (unless (eq argument last) (format stream ", ") (pprint-newline :fill stream))))) (unless (eq ep last) (format stream ", ") (pprint-newline :fill stream)))) (format stream ",") (pprint-newline :mandatory stream) (format stream "\"constraints\": ") (pprint-newline :mandatory stream) (pprint-logical-block (stream nil :prefix "[" :suffix "]") (loop with hconss = (psoa-h-cons mrs) with last = (first (last hconss)) for hcons in hconss for high = (hcons-scarg hcons) for low = (hcons-outscpd hcons) do (format stream "{\"relation\": \"qeq\", \"high\": ~a, \"low\": ~a}" (mrs-variable-output-json high :objectp nil) (mrs-variable-output-json low :objectp nil)) (pushnew high variables :test #'eq) (pushnew low variables :test #'eq) (unless (eq hcons last) (format stream ", ") (pprint-newline :fill stream)))) (format stream ",") (pprint-newline :mandatory stream) (format stream "\"variables\": ") (pprint-newline :mandatory stream) (pprint-logical-block (stream nil :prefix "{" :suffix "}") (loop with last = (first (last variables)) for variable in variables do (mrs-variable-output-json variable :objectp t :propertiesp propertiesp :stream stream) (unless (eq variable last) (format stream ", ") (pprint-newline :fill stream)))))))) (defun mrs-variable-output-json (variable &key stream objectp (propertiesp t)) (if (null stream) (with-output-to-string (stream) (mrs-variable-output-json variable :stream stream :objectp objectp :propertiesp propertiesp)) (cond (objectp (format stream "\"~a~a\": " (var-type variable) (var-id variable)) (pprint-logical-block (stream nil :prefix "{" :suffix "}") (format stream "\"type\": ~s" (var-type variable)) (when (and propertiesp (var-extra variable)) (format stream ", \"properties\": ") (pprint-newline :fill stream) (pprint-logical-block (stream nil :prefix "{" :suffix "}") (loop with properties = (var-extra variable) with last = (first (last properties)) for property in properties do (format stream "\"~a\": \"~(~a~)\"~@[, ~]" (extrapair-feature property) (extrapair-value property) (not (eq property last))) (unless (eq property last) (pprint-newline :fill stream))))))) (t (format stream "\"~a~a\"" (var-type variable) (var-id variable)))))) ;;; ;;; LaTeX output-type class ;;; (defun latex-escape-string (string) (if (and string (or (stringp string) (symbolp string))) (loop with string = (string string) with padding = 128 with length = (+ (length string) padding) with result = (make-array length :element-type 'character :adjustable nil :fill-pointer 0) for c across string when (member c '(#\_ #\% #\# #\{ #\}) :test #'char=) do (vector-push #\\ result) (vector-push c result) (when (zerop (decf padding)) (setf padding 42) (incf length padding) (setf result (adjust-array result length))) else do (vector-push c result) finally (return result)) string)) (defclass latex (output-type) ((context :initform nil) (variables :initform nil) (memory :initform nil))) (defmethod initialize-display-structure ((class latex) mrs &optional n) (declare (ignore mrs n))) (defmethod mrs-output-start-fn ((mrs latex))) (defmethod mrs-output-end-fn ((mrs latex))) (defmethod mrs-output-start-psoa ((mrs latex)) (with-slots (stream) mrs (format stream "\\siblock{"))) (defmethod mrs-output-top-h ((mrs latex) handle &optional properties type id) (declare (ignore properties type)) (with-slots (stream context) mrs ;; ;; temporarily prevent output of variable properties (top handle and index) ;; (push :mute context) (when (and handle *rel-handel-path*) (format stream "\\sh{~a}}" id)))) (defmethod mrs-output-index ((mrs latex) index &optional properties type id) (declare (ignore properties)) (with-slots (stream) mrs (when index (format stream "{\\svar{~a}{~a}{}}" type id)))) (defmethod mrs-output-start-liszt ((mrs latex)) (declare (special *already-seen-vars*)) ;; ;; because we do not include the (illegitimate) index in LaTeX output (at ;; least not by default), we need to reset the set of seen variables at this ;; point. ;; ;; AAC - included index now, as with other MRS output, following decision ;; 3017625 at the DELPH-IN Summit, but left the reset here ;; because better not to display the properties on the index in this ;; format. ;; (setf *already-seen-vars* nil) (with-slots (stream context) mrs (format stream "{%~%") (setf context nil))) (defmethod mrs-output-var-fn ((mrs latex) variable &optional properties type id) (with-slots (stream context variables) mrs (format stream "{\\svar{~a}{~a}~@[{}~*~]" type id (or (null properties) (member variable variables :test #'equal) (eq (first context) :mute))) (pushnew variable variables :test #'equal))) (defmethod mrs-output-atomic-fn ((mrs latex) value) (with-slots (stream) mrs (format stream "{\\sconst{~a}" value))) (defmethod mrs-output-start-rel ((mrs latex) pred firstp class &optional lnk str) (declare (ignore firstp class str)) (with-slots (memory stream context) mrs (if (eq (first context) :ep) (format stream ",\\\\~%") (push :ep context)) (format stream " \\sep") (let* ((pred (string-downcase pred)) (pred (remove-right-sequence *sem-relation-suffix* pred)) (lnk (and lnk (output-lnk lnk :stream nil :format :latex)))) (setf memory (format nil "~a~@[~a~]" (latex-escape-string pred) lnk))))) (defmethod mrs-output-rel-handel ((mrs latex) handle &optional properties sort id) (declare (ignore handle properties sort)) (with-slots (stream memory) mrs (format stream "{~@[\\sh{~a}~]}{\\spred{~:[\\srule~;~(~a~)~]}}{%~%" id memory memory))) (defmethod mrs-output-label-fn ((mrs latex) label) (with-slots (stream context) mrs (if (eq (first context) :roles) (format stream "},~%") (push :roles context)) (format stream " \\srole{~:@(~a~)}" label))) (defmethod mrs-output-start-extra ((mrs latex) type) (declare (ignore type)) (with-slots (stream context) mrs (unless (eq (first context) :mute) (format stream "{")))) (defmethod mrs-output-extra-feat ((mrs latex) feature) (with-slots (stream context) mrs (unless (eq (first context) :mute) (if (eq (first context) :extras) (format stream ", ") (push :extras context)) (format stream "\\svp{~:@(~a~)}" feature)))) (defmethod mrs-output-extra-val ((mrs latex) value) (with-slots (stream context) mrs (unless (eq (first context) :mute) (format stream "{~(~a~)}" (latex-escape-string value))))) (defmethod mrs-output-end-extra ((mrs latex)) (with-slots (stream context) mrs (unless (eq (first context) :mute) (format stream "}") (when (eq (first context) :extras) (pop context))))) (defmethod mrs-output-end-rel ((mrs latex)) (with-slots (stream context) mrs (format stream "}}") (when (eq (first context) :roles) (pop context)))) (defmethod mrs-output-end-liszt ((mrs latex)) (with-slots (stream context) mrs (format stream "}") (when (eq (first context) :ep) (pop context)))) (defmethod mrs-output-start-h-cons ((mrs latex)) (with-slots (stream) mrs (format stream "~% {"))) (defmethod mrs-output-outscopes ((mrs latex) relation higher lower firstp higher-id higher-sort lower-id lower-sort) (declare (ignore higher lower firstp higher-sort lower-sort)) (when (string-equal relation "qeq") (with-slots (stream context) mrs (if (eq (first context) :hcons) (format stream ", ") (push :hcons context)) (format stream "\\sqeq{~a}{~a}" higher-id lower-id)))) (defmethod mrs-output-end-h-cons ((mrs latex)) (with-slots (stream) mrs (format stream "}"))) (defmethod mrs-output-end-psoa ((mrs latex))) ;;; ;;; maximally compact debugging output-type class - was `debug' but that clashes with ;;; the CL symbol ;;; (defclass terse (output-type) ((memory :initform nil))) (defmethod initialize-display-structure ((class terse) mrs &optional n) (declare (ignore mrs n))) (defmethod mrs-output-start-fn ((mrs terse))) (defmethod mrs-output-end-fn ((mrs terse))) (defmethod mrs-output-start-psoa ((mrs terse))) (defmethod mrs-output-top-h ((mrs terse) handle &optional properties type id) (declare (ignore properties type id)) (when (and handle *rel-handel-path*) (with-slots (id stream) mrs (format stream "~a:" handle)))) (defmethod mrs-output-index ((mrs terse) index &optional properties type id) (declare (ignore properties type id)) (when index (with-slots (id stream) mrs (format stream "~a:" index)))) (defmethod mrs-output-start-liszt ((mrs terse)) (with-slots (stream) mrs (format stream "{"))) (defmethod mrs-output-var-fn ((mrs terse) variable &optional properties type id) (declare (ignore properties type id)) (with-slots (stream memory) mrs (format stream "~:[ ~;~]~a" memory variable) (setf memory nil))) (defmethod mrs-output-atomic-fn ((mrs terse) value) (with-slots (stream memory) mrs (format stream "~:[ ~;~]~a" memory value) (setf memory nil))) (defmethod mrs-output-start-rel ((mrs terse) pred firstp class &optional lnk str) (declare (ignore firstp class str)) (with-slots (stream memory) mrs (setf memory (if pred (if (stringp pred) (format nil "~s~a" pred (output-lnk lnk :stream nil)) (format nil "~(~a~)~a" pred (output-lnk lnk :stream nil))) (format nil "_~a" (output-lnk lnk :stream nil)))) (format stream " "))) (defmethod mrs-output-rel-handel ((mrs terse) handle &optional properties sort id) (declare (ignore properties sort id)) (with-slots (stream memory) mrs (format stream "~@[~a~]:~a(" handle memory memory))) (defmethod mrs-output-label-fn ((mrs terse) label) (declare (ignore label))) (defmethod mrs-output-start-extra ((mrs terse) type) (declare (ignore type))) (defmethod mrs-output-extra-feat ((mrs terse) feature) (declare (ignore feature))) (defmethod mrs-output-extra-val ((mrs terse) value) (declare (ignore value))) (defmethod mrs-output-end-extra ((mrs terse))) (defmethod mrs-output-end-rel ((mrs terse)) (with-slots (stream) mrs (format stream ")"))) (defmethod mrs-output-end-liszt ((mrs terse)) (with-slots (stream) mrs (format stream " }"))) (defmethod mrs-output-start-h-cons ((mrs terse)) (with-slots (stream) mrs (format stream "{ "))) (defmethod mrs-output-outscopes ((mrs terse) relation higher lower firstp higher-id higher-sort lower-id lower-sort) (declare (ignore higher-id higher-sort lower-id lower-sort)) (with-slots (stream) mrs (format stream "~:[, ~;~]~a ~(~a~) ~a" firstp higher relation lower))) (defmethod mrs-output-end-h-cons ((mrs terse)) (with-slots (stream) mrs (format stream " }"))) (defmethod mrs-output-end-psoa ((mrs terse))) ;;; XML output class (quite similar to RMRS) (defclass mrs-xml (output-type) ()) ;;; ;;; ;;; (defmethod mrs-output-start-fn ((mrsout mrs-xml)) (with-slots (stream) mrsout (format stream "~%~%"))) (defmethod mrs-output-end-fn ((mrsout mrs-xml)) (with-slots (stream) mrsout (format stream "~%~%"))) (defmethod mrs-output-start-psoa ((mrsout mrs-xml)) nil) (defmethod mrs-output-top-h ((mrsout mrs-xml) handel-val &optional properties type id) (declare (ignore properties type handel-val)) (with-slots (stream) mrsout (format stream "