;;; -*- Mode: tdl; Coding: utf-8; -*-
;;;
;;; Copyright (c) 1994-2018
;;; Dan Flickinger, Rob Malouf, Emily M. Bender
;;; see LICENSE for conditions
;;;
;;; lexrinst.tdl
;;;
;;; Instances of lexical rules defined in lexrules.tdl
;;;
;;; Created: Ann Copestake, 30-Sept-97
;;;
;;; $Id: lexrinst.tdl 7043 2009-09-03 18:26:55Z oe $
;
; Subject-auxiliary inversion
; Did they arrive?
;
;
;
v_aux-sb-inv_dlr := sai_nonell_lexrule &
[ RNAME lsai ].
;
; Subject-auxiliary inversion with elided verbs
; Did they?
;
;
;
v_aux-sb-inv-ell_dlr := sai_ell_lexrule &
[ RNAME lsaie ].
;
; Conditional inversion
; Had he left, we'd have left.
;
;
;
v_cond-inv_dlr := cond_sai &
[ RNAME csai ].
;
; Addition of adverb as complement
; They did not arrive.
;
;
;
v_aux-advadd_dlr := adv_addition &
[ RNAME ladv ].
;;?? comment out
;
; Elided VP with negation
; They would not.
;
;
;
v_aux-neg-ell_dlr := adv_add_neg_ellipt &
[ RNAME lnav ].
;
; Elided VP compl, referentl subj
; He did.
;
;
;
v_aux-ell-ref_dlr := vp_ellipsis_ref &
[ RNAME lver ].
;
; Elided VP compl, expletive subj
; It did.
;
;
;
v_aux-ell-xpl_dlr := vp_ellipsis_expl &
[ RNAME lvex ].
;
; Contracted auxiliary, no subject-auxiliary inversion
; Kim'll arrive.
; Kim'll.
;
;
v_aux-cx-noinv_dlr := contracted_aux_noninv_lr &
[ RNAME lcx ].
;
; Nominal gerund of intrans verb
; Leaving was easy.
;
;
;
v_nger-intr_dlr := intrans_nominal_gerund &
[ RNAME lngi ].
;
; Nominal gerund of PP-comp verb
; Relying on Kim was wrong.
;
;
;
v_nger-pp_dlr := intrans_pp_nominal_gerund &
[ RNAME lngp ].
;
; Nominal gerund of trans verb
; The hiring of Kim was OK.
;
;
;
v_nger-tr_dlr := trans_nominal_gerund &
[ RNAME lngt ].
;
; Month name as determiner
; July tenth arrived.
;
;
;
n_det-mnth_dlr := month_det_lr &
[ RNAME lmd ].
;
; Weekday name as determiner
; We arrived Sunday morning.
;
;
;
n_det-wkdy_dlr := weekday_det_lr &
[ RNAME lwd ].
;
; Weekday name as determiner
; We arrived Sunday morning.
;
;
;
n_dom-ppof_dlr := dom_ppof_lr &
[ RNAME ldp ].
;
; Attrib adj from trans pred adj
; A similar cat arrived.
;
;
;
j_att_dlr := attr_adj_lr &
[ RNAME lja ].
;
; Attrib adj from intrans verb
; The sleeping cat stirred.
;
;
;
v_j-nb-intr_dlr := attr_verb_part_lr &
[ RNAME ljv ].
;
; Attr adj from trans prp verb
; The admiring crowd ran.
;
;
;
v_j-nb-prp-tr_dlr := attr_verb_part_tr_lr &
[ RNAME ljvt ].
;
; Attr adj from trans passive verb
; The hired consultant left.
;
;
;
v_j-nb-pas-tr_dlr := attr_verb_part_psv_lr &
[ RNAME ljvp ].
;
; Attr adj from passive verb+selPP
; The hoped for consultant left.
;
;
;
v_j-nb-pas-ptcl_dlr := attr_verb_part_ptcl_psv_lr &
[ RNAME ljvr ].
;
; Attr adj from intr verb, nme mod, passive participle
; The respected Abrams won.
;
;
;
v_j-nme-intr_dlr := attr_verb_part_intr_namemod_lr &
[ RNAME ljvn ].
;
; Attr adj from intr verb, nme mod, pres participle
; The smiling Abrams won.
;
;
;
v_j-nme-intr-prp_dlr := attr_verb_part_intr_namemod_prp_lr &
[ RNAME ljvnp ].
;
; Attr adj from trns verb, nme mod, passive participle
; Our admired Abrams smiled.
;
;
;
v_j-nme-tr_dlr := attr_verb_part_tr_namemod_lr &
[ RNAME ljnt ].
;
; Attr adj from trns verb, nme mod, pres participle
; Our winning Abrams smiled.
;
;
;
v_j-nme-tr-prp_dlr := attr_verb_part_tr_namemod_prp_lr &
[ RNAME ljntp ].
;
; Partitive NP, PP-of, num agrmt
; Some of us are ready.
;
;
;
det_prt-of-agr_dlr := part_ppof_agr_constr &
[ SYNSEM.LOCAL.CAT.VAL.COMPS.FIRST.--SIND.DEF +,
RNAME lpca ].
det_prt-indef_dlr_rbst := part_ppof_agr_constr &
[ SYNSEM.LOCAL.CAT.VAL.COMPS.FIRST.--SIND.DEF -,
RNAME lpcar,
GENRE robust ].
;; DPF 2018-11-09 - Restrict of-PP to DIV +, to block |each of my toy|
;;
;
; Partitive NP, PP-of, no agrmt
; Each of us is ready
;
;
;
det_prt-of-nagr_dlr := part_ppof_noagr_constr &
[ SYNSEM.LOCAL.CAT.VAL.COMPS.FIRST.--SIND.DIV +,
RNAME lpcn ].
det_prt-of-nagr_dlr_rbst := part_ppof_noagr_constr &
[ SYNSEM.LOCAL.CAT.VAL.COMPS.FIRST.--SIND.DIV -,
RNAME lpcn,
GENRE robust ].
;
; Partitive NP, no PP complement
; Most arrived. part_nocomp
;
;
;
det_prt-nocmp_dlr := part_nocomp_constr &
[ RNAME lpn ].
;
; Particle-NP reordering
; He looked the answer up.
;
;
;
v_np-prtcl_dlr := NP_particle_lr &
[ RNAME lnpp ].
;; |Kim picked up him|
v_pron-prtcl_dlr_rbst := NP_particle_lr_mal &
[ RNAME lnpp ].
;
; Dative shift alternation
; They gave the book to him.
;
;
;
v_dat_dlr := dative_shift_lr &
[ RNAME ldat ].
;
; it-subj Verb+NP to CP or VP comp
; It annoyed B that we left.
;
;
;
v_it-cp-vp_dlr := verb_it_cp_vp_lr &
[ RNAME lvcv ].
;
; Integer as minute name
; Ten sixteen is too late.
;
;
;
j_n-minut_dlr := minute_noprep_lr &
[ RNAME lmin ].
;
; Integer as minute name with PP comp
; Sixteen to ten is too late.
;
;
;
j_n-minut-p_dlr := minute_prep_lr &
[ RNAME lminp ].
;
; hour plus NP complement
; Ten sixteen is too late.
;
;
;
n_n-hour_dlr := hour_np_lr &
[ RNAME lhour ].
;; EDUC: exclude
#|
;
; Tag question auxiliary
; He arrived, didn't he?
;
;
;
v_aux-tag_dlr := tag &
[ RNAME ltag ].
|#
;
; Adj no-comps plus enough-compl
; A big enough cat arrived.
;
;
;
j_enough_dlr := enough_addition_nocomps &
[ RNAME leno ].
;
; Adj w/comps plus enough-compl
; A happy enough cat arrived.
;
;
;
j_enough-wc_dlr := enough_addition_wcomp &
[ RNAME lenc ].
;
; Tough-adj alternation
; B is tough to admire.
;
;
;
j_tough_dlr := tough_adj_lr &
[ RNAME ltgh ].
#|
;
; Adjective to adverb, intersective only
; Kim arrived slowly.
;
;
;
j_r-i_odlr :=
%suffix (* ly) (!ty !tily)
adj_to_adv_lr &
[ ND-AFF +,
DTR.SYNSEM.LOCAL.CAT.HEAD.MOD < synsem & [ LOCAL int_mod_local ] >,
SYNSEM.LOCAL.CAT.HEAD.MOD < synsem & [ LOCAL int_mod_local ] >,
RNAME ljri ].
|#
;
; Relax bipartite constraint
; The scissors isn't sharp.
;
;
;
n_bipart_dlr := bipart_lr &
[ RNAME lbpt ].
;; EDUC: exclude
#|
;
; Italicized word made into NP
; Some say /windshield/.
;
;
;
w_italics_dlr := foreign_lr &
[ RNAME lfw ].
|#
;
; Main verb inversion for quoting
; He left, said Kim.
;
;
;
v_inv-quot_dlr := inverted_quote_lr &
[ RNAME linq ].
;; Block to avoid spurious ambiguity as in |We allow to sleep|
; But now using for robust |spoke bye-bye|
;
; Verbs of saying with fragment substituted for CP complement
; Yes, said Kim.
;
;
;
v_cp-frag_dlr := cp_frag_lr &
[ RNAME lcpf ].
;
; Noun with |-ed| suffix as adj
; Long-eared sheep slept.
;
;
;
n_n-ed_odlr :=
%suffix (* ed) (!ty !tied) (e ed) (!t!v!c !t!v!c!ced)
noun_adj_lr &
[ ND-AFF +,
RNAME lnj ].
;
; pre- prefix on nouns
; The pre-war period endured.
;
;
;
j_n-pre_odlr :=
%prefix (* pre) (* pre-)
pre_noun_adj_lr &
[ ND-AFF +,
RNAME ljnp ].
;
; Verb with |re-| prefix
; He re-tied his shoe.
;
;
;
v_v-re_dlr :=
%prefix (* re) (* re-)
v_v-re_rule &
[ ND-AFF +,
RNAME lre,
SYNSEM.PHON.ONSET con,
C-CONT.RELS ].
;
; Verb with |pre-| prefix
; He pre-signed the check.
;
;
;
v_v-pre_dlr :=
%prefix (* pre) (* pre-)
v_v-pre_rule &
[ ND-AFF +,
RNAME lpre,
SYNSEM.PHON.ONSET con,
C-CONT.RELS ].
;
; Verb with |mis-| prefix
; He mis-tied his shoe.
;
;
;
v_v-mis_dlr :=
%prefix (* mis) (* mis-)
v_v-mis_rule &
[ ND-AFF +,
RNAME lmis,
SYNSEM.PHON.ONSET con,
C-CONT.RELS ].
;;;
;;; _fix_me_
;;; to make this rule functional, token mapping would have to not separate off
;;; |co-| (in `derivational_prefix_tmr'). however, doing that would then mean
;;; that either (a) we provide a prefixation rule for other parts of speech too
;;; (`co-author', maybe `co-educational') or minimally adjust existing lexical
;;; entries (currently MWEs); or (b) that we create a token-level ambiguity; i
;;; hesitate doing the latter. but maybe it would not be so bad, in the end?
;;; the same problem applies to other derivational rules, of course.
;;; (13-mar-09; oe)
;
; Verb with |co-| prefix
; He co-wrote the paper.
;
;
;
v_v-co_dlr :=
%prefix (* co-) (* co)
v_v-co_rule &
[ ND-AFF +,
RNAME lco,
SYNSEM.PHON.ONSET con,
C-CONT.RELS ].
;
; Verb with |un-| prefix
; He untied his shoe.
;
;
;
v_v-un_dlr :=
%prefix (* un) (* un-)
v_v-un_rule &
[ ND-AFF +,
RNAME lunv,
SYNSEM.PHON.ONSET voc,
C-CONT.RELS ].
;
; Verb with |counter-| prefix
; He counter-signed the bill.
;
;
;
v_v-counter_dlr :=
%prefix (* counter) (* counter-)
v_v-counter_rule &
[ ND-AFF +,
RNAME lctv,
SYNSEM.PHON.ONSET con,
C-CONT.RELS ].
;
; Verb with |over-| prefix
; He over-built the porch.
;
;
;
v_v-over_dlr :=
%prefix (* over) (* over-)
v_v-over_rule &
[ ND-AFF +,
RNAME lovtv,
SYNSEM.PHON.ONSET voc,
C-CONT.RELS ].
;
; Verb with |over-| prefix
; He over-built the porch.
;
;
;
v_v-under_dlr :=
%prefix (* under) (* under-)
v_v-over_rule &
[ ND-AFF +,
RNAME luvtv,
SYNSEM.PHON.ONSET voc,
C-CONT.RELS ].
;
; Verb with |out-| prefix
; He out-played his opponent.
;
;
;
v_v-out_dlr :=
%prefix (* out) (* out-)
v_v-out_rule &
[ ND-AFF +,
RNAME lotv,
SYNSEM.PHON.ONSET voc,
C-CONT.RELS ].
;
; Verb with |self-| prefix
; He was self-insured.
;
;
;
v_v-self_dlr :=
%prefix (* self) (* self-)
v_v-self_rule &
[ ND-AFF +,
RNAME lsfv,
SYNSEM.PHON.ONSET con,
C-CONT.RELS ].
;
; Verb with |cross-| prefix
; He cross-examined the witness.
;
;
;
v_v-cross_dlr :=
%prefix (* cross) (* cross-)
v_v-cross_rule &
[ ND-AFF +,
RNAME lcsv,
SYNSEM.PHON.ONSET con,
C-CONT.RELS ].
;
; Noun with |co-| prefix
; Our co-teacher arrived.
;
;
;
n_n-co_dlr :=
%prefix (* co) (* co-)
n_n-co_rule &
[ ND-AFF +,
RNAME lnco,
SYNSEM.PHON.ONSET con,
C-CONT.RELS ].
;
; Noun with |co-| prefix, non-inflecting
; Our co-derivatives group arrived.
;
;
;
n_n-co-ni_dlr :=
%prefix (* co) (* co-)
n_n-co-ni_rule &
[ ND-AFF +,
RNAME lncon,
SYNSEM.PHON.ONSET con,
C-CONT.RELS ].
;
; Noun with |counter-| prefix
; The counter-proposal arrived.
;
;
;
n_n-counter_dlr :=
%prefix (* counter) (* counter-)
n_n-counter_rule &
[ ND-AFF +,
RNAME lctn,
SYNSEM.PHON.ONSET con,
C-CONT.RELS ].
;
; Noun with |counter-| prefix, non-inflecting
; The counter-narcotics team arrived.
;
;
;
n_n-counter-ni_dlr :=
%prefix (* counter) (* counter-)
n_n-counter-ni_rule &
[ ND-AFF +,
RNAME lctnn,
SYNSEM.PHON.ONSET con,
C-CONT.RELS ].
;
; Noun with |mini-| prefix
; The mini-car arrived.
;
;
;
n_n-mini_dlr :=
%prefix (* mini) (* mini-)
n_n-mini_rule &
[ ND-AFF +,
RNAME lctn,
SYNSEM.PHON.ONSET con,
C-CONT.RELS ].
;
; Noun with |mini-| prefix, non-inflecting
; The mini-car transporter arrived.
;
;
;
n_n-mini-ni_dlr :=
%prefix (* mini) (* mini-)
n_n-mini-ni_rule &
[ ND-AFF +,
RNAME lctnn,
SYNSEM.PHON.ONSET con,
C-CONT.RELS ].
;
; Adjective with |co-| prefix
; The co-educational hall opened.
;
;
;
j_j-co_dlr :=
%prefix (* co-) (* co)
j_j-co_rule &
[ ND-AFF +,
RNAME ljco,
SYNSEM.PHON.ONSET con,
C-CONT.RELS ].
;
; Adjective with |un-| prefix
; The unhappy cat arose.
;
;
;
j_j-un_dlr :=
%prefix (* un-) (* un)
j_j-un_rule &
[ ND-AFF +,
RNAME lunj,
SYNSEM.PHON.ONSET voc,
C-CONT.RELS ].
;
; Adjective with |non| prefix
; The nonlinear solution failed.
;
;
;
j_j-non_dlr :=
%prefix (* non)
j_j-non_rule &
[ ND-AFF +,
RNAME lnnj,
SYNSEM.PHON.ONSET con,
C-CONT.RELS ].
;;; From arboretum/mal-inflr.tdl
;; Disagreement rules, one for each direction. Pair synsem with
;; "wrong" forms: The dog bark/the dogs barks.
;;
;; Constrain this one to only apply to pronominal subject, to avoid spurious
;; analysis using both this rule and the mal_plur_noun_irule
;; DPF 25-jun-10 - But we also want to catch e.g. "my knees hurts", so let's
;; try blocking --BARE +, to avoid the above spuriosity.
;; Also block clauses headed by such verbs from undergoing cl_np-wh_c rule
;; DPF 2013-05-10 - But [NORM no_rel] prevents conjoined robust forms, as in
;; |people arrives and arises|. So remove, and monitor.
;;
non_third_sg_fin_v_rbst :=
%suffix (!s !ss) (!ss !ssses) (ss sses) (!ty !ties) (ch ches) (sh shes) (x xes) (z zes)
lex_rule_infl_affixed &
[ GENRE robust,
ND-AFF +,
SYNSEM.LOCAL non_third_sg_fin_verb &
[ CAT [ HEAD.--MALN3SG +,
VAL.SUBJ < [ LOCAL.CAT.HEAD [ --BARE -,
MINORS.MIN nonpart_nom_rel ] ] > ]],
RNAME mn3s ].
;; DPF 2010-08-16 - Block subject extraction, to avoid spurious analysis for
;; "What do Kim and Abrams ..."
;; DPF 2017-09-06 -Block time NPs as subjects, to avoid robust analysis for
;; |ten grow in the garden|
;; DPF 2017-10-05 - Block partitive subjects, for |his admire cats|, by making
;; subj HEAD non_partn.
;; DPF 2018-02-15 - Re 2017-10-05: But ordinary pronouns are also HEAD partn,
;; so can't block partitives this way.
;; DPF 2018-10-02 - Remove SUBJ..--BARE + so we can trigger agreement mismatch
;; also for nouns that block robust bare plural, as |the class arise|
;;
third_sg_fin_v_rbst := lex_rule_infl_affixed &
[ GENRE robust,
ND-AFF -,
ORTH #stem,
DTR [ ORTH #stem,
SYNSEM.LOCAL.CAT [ HEAD.--MAL3SG +,
VAL.SUBJ < expressed_synsem &
[ LOCAL [ AGR.PNG.PN 3s,
CAT.HEAD supnoun ],
--SIND nonconj_ref-ind & [ SORT entity],
PUNCT.RPUNCT comma_or_no_punct ] > ] ],
SYNSEM.LOCAL third_sg_fin_verb,
RNAME m3s ].
;; DPF 10-May-04 - We take plural marking on noun as intended (not to be
;; corrected), so only have one mal infl-rule for nouns to correct
;; 'two dog bark' to 'two dogs bark'. We will need a statistical preference
;; mechanism to choose one of the two possible corrections for 'dog bark':
;; either 'dogs bark' or 'a/the dog barks'. But have to have both, since
;; 'he bark' should presumably get corrected to 'he barks' (not 'they bark').
;; DPF 07-feb-10 - Changed DTR..MIN norm_nom_rel to reg_nom_rel, so it also
;; applies to measure nouns, as in "they ran twenty six mile."
;; Note that CASE on dtr must be nom to avoid spurious ambiguity for e.g.
;; direct objects where there is no constraint on number.
;; DPF 30-mar-10 - Restrict this to only apply when the determiner is overt,
;; to avoid spurious ambiguity for e.g. "she told her brother borrow her book"
;; where `brother' formerly got made a plural. So now we assume that number
;; on nouns is as the writer intended, unless there is a determiner present,
;; which might indicate competing number, as in "most thing are important"
;; the verb to match robustly when needed.
;; DPF 07-apr-10 - But still getting too much spurious ambiguity, as in
;; "His soup is". So restrict further to just deictic dets for now.
;; DPF 2018-03-23 - Re 07-apr-10: Expand dtr's SPR..--MIN from
;; demonstrative_q_rel to num_or_demon_q_rel so we can still get
;; |three dog barked|
;; DPF 2018-07-31 - Re 07-apr-10: We would like to get error for
;; |our five sense|, so tried removing constraint on SPR..--MIN, but then
;; we get spurious robust analysis for |A dog bit him|. So FIX later.
;; DPF 2018-10-03 - Re 07-feb-10: But this prevents |we admire these cat|,
;; and since we now require a num-or-demon specifier, we drop CASE nom.
;; Also, generalize --MIN from reg_nom_rel to reg_or_temp_nom_rel, so we also
;; get robust |we enjoyed these year|.
;;
plur_noun_irule_rbst := lex_rule_infl_affixed &
[ GENRE robust,
ND-AFF -,
ORTH #stem,
SYNSEM.LOCAL [ CAT.HEAD.--BARE +,
AGR.PNG png-reg ],
DTR [ ORTH #stem,
SYNSEM.LOCAL.CAT [ HEAD.MINORS.MIN reg_or_temp_nom_rel,
VAL.SPR < canonical_synsem &
[ --MIN num_or_demon_q_rel ] > ] ],
SYNSEM.LOCAL plur_noun,
RNAME mpln ].
; For |Kim, Abrams(,) and Browne|
w_paren_comma-nf_plr :=
%suffix (!. !.\(,\))
punctuation_comma_rule.
;; For prefixed comma as in |yesterday ,we arose|
;;
w_comma-prefix_plr_rbst :=
%prefix (!. ,!.)
basic_punctuation_comma_rule &
[ GENRE robust ].
;; For sandwiched comma: |the tall,green tree|
w_comma-sdwch_plr := never_unify_rule.
w_comma-sdwch_plr_rbst :=
%suffix (!q !q⸴)
punctuation_comma_sandwich_rule &
[ RNAME lpcs,
GENRE robust ].
v_prp-nf_olr := never_unify_le.
j_vp_bse_dlr_rbst := adj_vp_bse_mal_lr &
[ RNAME ljvb ].
;; For e.g. |informations|
;;
n_pl-mass_olr_rbst :=
%suffix (!s !ss) (!ss !ssses) (es eses) (ss sses) (!ty !ties) (ch ches) (sh shes) (x xes) (z zes)
lex_rule_plural_mass &
[ ND-AFF +,
RNAME lplm ].
;; For |deers, fishes|
n_pl_olr_rbst :=
%suffix (* nevermatch)
n_pl_inflrule &
[ ND-AFF +,
SYNSEM mass_or_count_synsem &
[ LOCAL plur_noun & [ AGR.PNG png-irreg ] ],
RNAME lplr,
GENRE robust ].
;; For -s where other productive forms are needed, e.g. |-ies| and |ches|
n_pl-reg_olr_rbst :=
%suffix (!ss !sss) (es ess) (ss sss) (!ty !tys) (ch chs) (sh shs) (x xs) (z zs)
n_pl_inflrule &
[ ND-AFF +,
SYNSEM mass_or_count_synsem &
[ LOCAL plur_noun & [ AGR.PNG png-reg ] ],
RNAME lplrr,
GENRE robust ].
;; Block robust comma, to avoid spurious analysis of "the cat, arrived."
;w_comma-nf_plr :=
;%suffix (!. !.,)
;punctuation_comma_informal_rule &
; [ SYNSEM.LOCAL.CAT.HEAD no_head,
; RNAME lpcr ].
;; DPF 2017-09-28 - Use for irregular past tense forms, so we can trigger
;; robust analysis for e.g. |he had went| but not for |he had arrived|.
v_pst_olr :=
%suffix (* ed) (!ty !tied) (e ed) (!t!v!c !t!v!c!ced)
v_pst_inflrule &
[ ND-AFF +,
ALTS.TNS-ID -,
SYNSEM.LOCAL past_or_subj_verb &
[ CAT.HEAD.TAM.IRR-TENSE - ],
RNAME lvpt ].
v_pst-irreg_olr :=
%suffix (* nevermatch)
v_pst_inflrule &
[ ND-AFF +,
SYNSEM.LOCAL past_or_subj_verb &
[ CAT.HEAD.TAM.IRR-TENSE + ],
RNAME lvpti ].
;; For wrong regular past inflection of irregular verbs (|buyed| for |bought|)
;;
v_pst_olr_rbst :=
%suffix (* nevermatch)
v_pst_inflrule &
[ GENRE robust,
ND-AFF +,
SYNSEM.LOCAL past_or_subj_verb & [ CAT.HEAD.--MALPAST + ],
RNAME lvptr ].
;; If tense of main verb and that of embedded clause don't match, complain,
;; as per TOEFL: |I felt that he is friendly|. May need to revisit this and
;; FIX
;;
v_pst_scomp_olr_rbst :=
%suffix (* ed) (!ty !tied) (e ed) (!t!v!c !t!v!c!ced)
v_pst_inflrule &
[ ND-AFF +,
ALTS.TNS-ID +,
SYNSEM basic_cp_prop+ques_verb &
[ LOCAL past_or_subj_verb &
[ CAT.VAL.KCMP [ LOCAL.CAT [ HEAD verbal &
[ VFORM fin,
TAM [ TENSE nonpast,
UNSP-TENSE - ] ],
MC - ],
--SIND.E.SAME-PAST -,
LEX - ] ] ],
RNAME lvpts,
GENRE robust ].
v_psp_olr_rbst :=
%suffix (* nevermatch)
v_psp_inflrule &
[ GENRE robust,
ND-AFF +,
SYNSEM.LOCAL psp_verb,
RNAME lvppr ].
v_pas_odlr_rbst :=
%suffix (* nevermatch)
v_pas-norm_lexrule &
[ GENRE robust,
ND-AFF +,
DTR.SYNSEM trans_subst &
[ LOCAL [ CAT.VAL.COMPS [ FIRST [ LOCAL.CONT #objcont,
--SIND #objind,
NONLOC #ononloc ],
REST #comps ] ],
LKEYS.KEYREL #keyrel ],
SYNSEM [ LOCAL [ CAT [ VAL [ SUBJ < [ LOCAL.CONT #objcont,
--SIND #objind,
NONLOC #ononloc ] >,
COMPS.REST #comps ] ],
CONT [ HOOK.XARG #objind ] ],
LKEYS.KEYREL #keyrel ],
RNAME lvpar ].
v_pas-p_odlr_rbst :=
%suffix (* nevermatch)
prep_passive_verb_lr &
[ GENRE robust,
ND-AFF +,
RNAME lvper ].
v_pas-p-t_odlr_rbst :=
%suffix (* nevermatch)
prep_passive_trans_verb_lr &
[ GENRE robust,
ND-AFF +,
RNAME lvpfr ].
v_pas-prt-t_odlr_rbst :=
%suffix (* nevermatch)
prep_passive_ptcl_verb_lr &
[ GENRE robust,
ND-AFF +,
RNAME lvpgr ].
v_pas-dat_odlr_rbst :=
%suffix (* nevermatch)
basic_passive_verb_lr &
[ GENRE robust,
ND-AFF +,
DTR [ SYNSEM basic_ditrans_subst &
[ LOCAL [ CAT.VAL [ SUBJ < [ --SIND #subjind,
NONLOC #snonloc ] >,
COMPS < [ LOCAL.CONT #objcont,
--SIND #objind,
NONLOC #ononloc ],
#npcomp > ] ],
LKEYS.KEYREL #keyrel ] ],
SYNSEM [ LOCAL [ CAT [ VAL [ SUBJ < [ LOCAL.CONT #objcont,
--SIND #objind,
NONLOC #ononloc ] >,
COMPS < #npcomp,
synsem &
[ LOCAL local &
[ CAT [ HEAD prep &
[ MINORS.MIN _by_p_cm_rel ],
VAL [ SUBJ < >,
SPR *olist*,
COMPS < > ] ],
CONT.HOOK.INDEX #subjind ],
NONLOC #snonloc,
OPT + ] > ] ],
CONT [ HOOK.XARG #objind ] ],
LKEYS.KEYREL #keyrel ],
RNAME lvdpr ].
v_pas-cp_odlr_rbst :=
%suffix (* nevermatch)
v_pas-cp_lexrule &
[ GENRE robust,
ND-AFF +,
DTR.SYNSEM cp_passivable_verb &
[ LOCAL.CAT.VAL [ COMPS #comps,
KCMP #kcmp ] ],
SYNSEM passive_atrans_synsem &
[ LOCAL.CAT [ VAL [ COMPS.REST #comps,
KCMP #kcmp ] ] ],
RNAME lvcpr ].
v_prp_olr_rbst :=
%suffix (* nevermatch)
v_prp_inflrule &
[ GENRE robust,
ND-AFF +,
SYNSEM.LOCAL prp_verb,
RNAME lvprr ].
v_3s-fin_olr_rbst :=
%suffix (* nevermatch)
v_3s-fin_inflrule &
[ GENRE robust,
ND-AFF +,
SYNSEM.LOCAL third_sg_fin_verb,
RNAME lvsgr ].
;; For e.g. |informations|
;;
aj_comp_equat_olr_rbst := lex_rule_compar_equative &
[ ND-AFF -,
RNAME ljce ].
aj_vp_inf-prp_olr_rbst := adj_vp_inf_prp_mal_lr &
[ ND-AFF -,
RNAME ljip ].
;; |Kim is easy to talk to her|
aj_vp_i-seq_le_rbst := adj_vp_inf_seq_mal_lr &
[ ND-AFF -,
RNAME ljip ].
v_cp-frag_dlr := never_unify_le.
;; For initial capital letter
w_hasinitcap_dlr := has_initial_cap_rule.
w_noinitcap_dlr_rbst := missing_initial_cap_rule.
w_ne_cap_dlr := named_entity_cap_rule.