;;; Grammar of Thai
;;; created at:
;;;     Mon Feb 02 04:33:38 UTC 2009
;;; based on Matrix customization system version of:
;;;     Mon Feb  2 01:32:50 UTC 2009


;;;--------------------------------------------------------------------------
;;; Features
;;;--------------------------------------------------------------------------

;;; 02-14-2009 gcs added Thai numeric classifier head value
numcl := +cd.

;;; 02-14-2009 gcs added LEFTCOMP

head :+
    [ FORM form,
      PRD bool,
      LEFTCOMP bool,
      CLASSIF string ].
      
;;; Person

person := *top*.
1st := person.
2nd := person.
3rd := person.

;;; Number

number := *top*.
sg := number.
pl := number.

;;; Gender

gender := *top*.
animate := gender.
masculine := animate.
feminine := animate.
inanimate := gender.

;;; Person-Number-Gender

png :+ [ PER person,
    NUM number,
    GEND gender ].

;;; Form
;;; 2009-02-21 gcs
;;; mv-form - main verb
;;; pre-fin - pre-finite stage, has combined with pre-aux
;;; finite - finite stage, has combined with (pre- and) post aux

form := *top*.
sealed := form.
any-form := form.
post-aux := any-form.
mv-or-pre-aux := any-form.
mv-form := mv-or-pre-aux.
pre-aux := mv-or-pre-aux.

;;; Aspect

aspect :+ [ SOON bool,
            PROGRESS bool,
            GET bool,
            EVER bool,
            ALREADY bool,
            CONTIN bool,
            SEMIPERFV bool,
            PERF bool,
            PERFV bool ].

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;;; Lexical types
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

;;;--------------------------------------------------------------------------
;;; Nouns
;;;--------------------------------------------------------------------------

noun-lex := basic-noun-lex & basic-one-arg & no-hcons-lex-item &
  [ SYNSEM.LOCAL.CAT.VAL [ SPR < #spr &
                                 [ LOCAL.CAT.HEAD det ] >,
                           COMPS < >,
                           SUBJ < >,
                           SPEC < > ],
    ARG-ST < #spr > ].

; Nouns which cannot take specifiers mark their SPR requirement
; as OPT +.  Making the non-head daughter OPT - in this rule
; keeps such nouns out.

base-noun-lex := noun-lex &
  [ SYNSEM.LOCAL.CONT.HOOK.INDEX.PNG.PER 3rd ].

; Names

prop-noun-lex := noun-lex & [ SYNSEM.LKEYS.KEYREL named-relation ].

no-spr-noun-lex := noun-lex &
  [ SYNSEM.LOCAL.CAT.VAL.SPR < [ OPT + ] > ].

; 02-08-2009 gcs added 'overt-pronoun'
; 02-11-2009 gcs moved common predication for pronouns here
overt-pronoun := no-spr-noun-lex &
  [ SYNSEM.LKEYS.KEYREL.PRED "_pronoun_n_rel" ].
             
non-demonst-pronoun-lex := overt-pronoun &
  [ SYNSEM.LOCAL.CONT.HOOK.INDEX [ SPECI +,
                                   COG-ST activ-or-more ] ].
  
animate-pronoun-lex := non-demonst-pronoun-lex & 
  [ SYNSEM.LOCAL.CONT.HOOK.INDEX.PNG.GEND animate ].

m1sg-pronoun-lex := animate-pronoun-lex &
  [ SYNSEM.LOCAL.CONT.HOOK.INDEX.PNG [ PER 1st,
                                       NUM sg,
                                       GEND masculine ] ].

f1sg-pronoun-lex := animate-pronoun-lex &
  [ SYNSEM.LOCAL.CONT.HOOK.INDEX.PNG [ PER 1st,
                                       NUM sg,
                                       GEND feminine ] ].

2sg-pronoun-lex := animate-pronoun-lex &
  [ SYNSEM.LOCAL.CONT.HOOK.INDEX.PNG.PER 2nd ].

3sg-pronoun-lex := animate-pronoun-lex &
  [ SYNSEM.LOCAL.CONT.HOOK.INDEX.PNG.PER 3rd ].

1pl-pronoun-lex := animate-pronoun-lex &
  [ SYNSEM.LOCAL.CONT.HOOK.INDEX.PNG [ PER 1st,
                                       NUM pl ] ].
  
ia-3sg-pronoun-lex := non-demonst-pronoun-lex &
  [ SYNSEM.LOCAL.CONT.HOOK.INDEX.PNG [ PER 3rd,
                                       GEND inanimate ] ].

; 02-19-2009 gcs added 'demonst-pronoun-lex' placeholder
; 03-07-2009 gcs no longer a placeholder
demonst-pronoun-lex := overt-pronoun &
  [ SYNSEM.LOCAL.CONT.HOOK.INDEX [ SPECI -,
                                   COG-ST activ+fam,
                                   PNG [ PER 3rd,
                                         GEND inanimate ] ] ].
                                       
;;;--------------------------------------------------------------------------
;;; Adjectives
;;;
;;; 02-05-2009 gcs added adjective type 'adjective-lex'
;;; 02-12-2009 gcs added 'number-name-relation'
;;;--------------------------------------------------------------------------
              
attr-adjective-lex := basic-adjective-lex & intersective-mod-lex & norm-ltop-lex-item &
    [ SYNSEM [ LOCAL [ CAT [ HEAD [ PRD -,
                                    MOD < [ LOCAL.CAT [ HEAD noun,
                                                        VAL.SPR cons ] ] > ],
                             VAL [ SPR < >,
                                   SUBJ < >,
                                   COMPS < >,
                                   SPEC < > ],
                             POSTHEAD + ],
                       CONT.HOOK [ INDEX #ix,
                                   XARG #arg ] ],
               LKEYS.KEYREL [ ARG0 #ix,
                              ARG1 #arg ] ] ].
                         
pred-adj-lex := local-change-only-lex-rule &
  [ SYNSEM.LOCAL [ CAT [ HEAD adj & [ PRD +,
                                      MOD < > ],
                         VAL [ SPR < >,
                               SUBJ < [ OPT +, 
                                        LOCAL [ CAT [ HEAD noun,
                                                      VAL.SPR < > ],
                                                CONT.HOOK.INDEX #ind ] ] >,
                               COMPS < >,
                               SPEC < > ],
                         POSTHEAD #ph ],
                   CONT.HOOK #hk ],
    DTR.SYNSEM [ LOCAL [ CAT [ HEAD adj &
                                    [ MOD < [ LOCAL.CONT.HOOK.INDEX #ind ] > ],
                               VAL [ SPR < >,
                                     SUBJ < >,
                                     COMPS < >,
                                     SPEC < > ],
                               POSTHEAD #ph ],
                         CONT.HOOK #hk ] ] ].
			   
;;;--------------------------------------------------------------------------
;;; Adverbs
;;;
;;; 02-05-2009 gcs added adverb type 'adverb-lex'
;;;--------------------------------------------------------------------------
			   
adverb-lex := basic-adverb-lex & intersective-mod-lex &
  [ SYNSEM.LOCAL.CAT [ HEAD.MOD < [ LOCAL.CAT [ HEAD verb,
                                                VAL.COMPS < > ] ]>,
                       VAL [ SPR < >,
                             SUBJ < >,
                             COMPS < >,
                             SPEC < > ] ] ].
				 
;;;--------------------------------------------------------------------------
;;; Verbs
;;; 02-12-2009 gcs added 'ditransitive-verb-lex' and 'no-drop-dt-verb-lex'
;;;--------------------------------------------------------------------------

; verb-lex is HC-LIGHT - to allow us to pick out
; 
;     lexical Vs for V-level attachment of negative adverbs.

verb-lex := lex-item &
  [ SYNSEM.LOCAL.CAT [ HEAD verb,
                       HC-LIGHT - ] ].

main-verb-lex := verb-lex & basic-verb-lex &
  [ SYNSEM.LOCAL [ CAT [ HEAD [FORM mv-form ],
                         VAL [ SPR < >,
                               SPEC < >,
                               SUBJ < #subj > ] ],
                   CONT.HOOK.XARG #xarg ],
    ARG-ST.FIRST #subj &
                 [ LOCAL [ CAT.VAL [ SPR < >,
                                     COMPS < > ],
                           CONT.HOOK.INDEX #xarg ] ] ].

intransitive-verb-lex := main-verb-lex & intransitive-lex-item &
    [ SYNSEM.LOCAL.CAT.VAL.COMPS < >,
      ARG-ST.FIRST.LOCAL.CAT.HEAD noun ].

transitive-verb-lex := main-verb-lex & transitive-lex-item &
    [ SYNSEM.LOCAL.CAT.VAL.COMPS < #comps >,
      ARG-ST < [ LOCAL.CAT.HEAD noun ], 
               #comps & [ LOCAL.CAT [ HEAD +nd,
                                      VAL [ SPR < >,
                                            COMPS < > ] ] ] > ].
                           
ditransitive-verb-lex := main-verb-lex & ditransitive-lex-item &
    [ SYNSEM.LOCAL.CAT.VAL.COMPS < #c1, #c2 >,
      ARG-ST < [ LOCAL.CAT.HEAD noun ],
               #c1 & [ LOCAL.CAT [ HEAD noun,
                                   VAL [ SPR < >,
                                         COMPS < > ] ] ] ,
               #c2 & [ LOCAL.CAT [ HEAD +np,
                                   VAL [ SPR < >,
                                         COMPS < > ] ] ] > ].
                                        
emb-clause-verb-lex := main-verb-lex & clausal-second-arg-trans-lex-item &
    [ SYNSEM.LOCAL.CAT.VAL.COMPS < #claus >,
      ARG-ST < [ LOCAL.CAT.HEAD noun ], 
               #claus & [ LOCAL [ CAT [ HEAD comp,
                                        VAL [ SPR < >,
                                              COMPS < > ] ],
                                  CONT.HOOK.INDEX.SF prop-or-ques ] ] > ].
											
i-verb-lex := intransitive-verb-lex.

drop-t-verb-lex := transitive-verb-lex & [ ARG-ST < [], [ OPT-CS type-id ] > ].

no-drop-t-verb-lex := transitive-verb-lex & [ SYNSEM.LOCAL.CAT.VAL.COMPS < [OPT -] > ].

no-drop-dt-verb-lex := ditransitive-verb-lex & [ SYNSEM.LOCAL.CAT.VAL.COMPS < [OPT -] , [OPT -] > ].

drop-io-dt-verb-lex := ditransitive-verb-lex & [ SYNSEM.LOCAL.CAT.VAL.COMPS < [OPT -] , [] > ].

emb-q-verb-lex := emb-clause-verb-lex & [ ARG-ST <	[], [ LOCAL [ CAT.MC -,
                                                                  CONT.HOOK.INDEX.SF ques ] ] > ].

emb-d-verb-lex := emb-clause-verb-lex & [ ARG-ST <	[], [ LOCAL.CONT.HOOK.INDEX.SF prop ] > ].

locative-verb-lex := main-verb-lex & trans-first-arg-raising-lex-item-1 &
  [ SYNSEM.LOCAL [ CAT.VAL [ SUBJ < #subj >,
                             COMPS < #comps & [OPT -] >,
                             SPR < >,
                             SPEC < > ],
                   CONT.HOOK.XARG #xarg ],
    ARG-ST < #subj &
             [ LOCAL [ CONT.HOOK.INDEX #xarg,
                       CAT [ VAL [ SPR < >,
                                   COMPS < > ],
                             HEAD noun ] ] ],
             #comps &
             [ LOCAL.CAT [ VAL [ COMPS < > ],
                           HEAD adp ] ] > ].
                           
negative-copula-lex := verb-lex & norm-ltop-lex-item & basic-two-arg &
  [ SYNSEM [ LOCAL [ CAT [ HEAD verb & [ FORM mv-form ],
                           VAL [ SUBJ < #subj >,
                                 COMPS < #comps >,
                                 SPR < >,
                                 SPEC < > ] ],
                     CONT [ HCONS <! qeq & [ HARG #harg,
                                             LARG #larg ] !>,
                            HOOK.INDEX #this,
                            RELS <! relation , arg12-ev-relation & [ PRED "_be_v_id_rel", 
                                                            LBL #larg,
                                                            ARG0 #this,
                                                            ARG1 #xarg,
                                                            ARG2 #yarg ] !> ] ],
             LKEYS.KEYREL event-relation & [ ARG1 #harg ] ],
    ARG-ST < #subj &
             [ LOCAL [ CONT.HOOK.INDEX #xarg,
                       CAT [ VAL [ SPR < >,
                                   COMPS < > ],
                             HEAD noun ] ] ],
             #comps &
             [ LOCAL [ CAT [ VAL [ SPR < >,
                                   COMPS < > ],
                             HEAD noun ],
                       CONT.HOOK [ INDEX #yarg,
                                   XARG #xarg ] ] ] > ].
                           
                           
 causative-verb-lex := main-verb-lex & ditransitive-lex-item &
    [ SYNSEM.LOCAL.CAT.VAL.COMPS < #c1 & [OPT -], #c2 & [OPT -] >,
      ARG-ST < [ LOCAL.CAT.HEAD noun ],
               #c2 & [ LOCAL.CAT [ HEAD noun,
                                   VAL [ SPR < >,
                                         COMPS < > ] ] ] ,
               #c1 & [ LOCAL.CAT [ HEAD noun,
                                   VAL [ SPR < >,
                                         COMPS < > ] ] ] > ].


;;;--------------------------------------------------------------------------
;;; Adpositions
;;;--------------------------------------------------------------------------

case-marker-p-lex := basic-one-arg & raise-sem-lex-item &
  [ SYNSEM.LOCAL.CAT [ HEAD adp &
                            [ MOD < > ],
                       VAL [ SPR < >,
                             SUBJ < >,
                             COMPS < #comps >,
                             SPEC < > ] ],
    ARG-ST < #comps &
             [ LOCAL.CAT [ HEAD noun,
                           VAL.SPR < > ] ] > ].
                           
prep-lex := basic-int-mod-adposition-lex & transitive-lex-item & 
  [ SYNSEM [ LOCAL [ CAT [ HEAD.MOD < [ LOCAL.CAT [ HEAD +nv,
                                                    VAL.SPR < > ] ] >,
                           VAL [ SPR < >,
                                 SUBJ < >,
                                 COMPS < #comps >,
                                 SPEC < > ] ],
                     CONT.HOOK.XARG #xa ],
             LKEYS.KEYREL.ARG1 #xa ],
    ARG-ST < [ ],
             #comps & [ OPT -,
               LOCAL.CAT [ HEAD noun,
                           VAL.SPR < > ] ] > ].

;;;--------------------------------------------------------------------------
;;; Auxiliaries
;;;--------------------------------------------------------------------------

subj-raise-aux := verb-lex & trans-first-arg-raising-lex-item &
  [ SYNSEM.LOCAL [ CAT.VAL [ SUBJ < #subj >,
                             COMPS < #comps >,
                             SPR < >,
                             SPEC < > ],
                   CONT.HOOK.XARG #xarg ],
    ARG-ST < #subj &
             [ LOCAL [ CONT.HOOK.INDEX #xarg,
                       CAT [ VAL [ SPR < >,
                                   COMPS < > ],
                             HEAD noun ] ] ],
             #comps &
             [ LOCAL.CAT [ VAL [ SUBJ < [  ] >,
                                 COMPS < > ],
                           HEAD +vj ] ] > ].

subj-raise-aux-with-pred := subj-raise-aux & norm-sem-lex-item & trans-first-arg-raising-lex-item-1 &
  [ ARG-ST < [  ], [  ] > ].

; To keep the semantically empty ones from spinning on
; generation, require complement to be [AUX -].  The
; FORM feature might be enough in the starter grammars,
; but I don't want to rely on this.  Then again, [ AUX - ]
; might not be true.  Be sure to put in a comment.

subj-raise-aux-no-pred := subj-raise-aux & raise-sem-lex-item.

imminent-aux-lex := subj-raise-aux-no-pred &
  [ SYNSEM.LOCAL [ CAT [ HEAD [ FORM pre-aux ],
                         VAL.COMPS < [ OPT -,
                                       LOCAL [ CAT.HEAD.FORM mv-or-pre-aux,
                                               CONT.HOOK.INDEX.E.ASPECT #asp ] ] > ],
                   CONT.HOOK.INDEX.E.ASPECT #asp ] ].

tam1-aux-lex := subj-raise-aux-no-pred &
  [ SYNSEM.LOCAL [ CAT [ HEAD [ FORM pre-aux,
                                LEFTCOMP - ],
                         VAL.COMPS < [ OPT -,
                                       LOCAL [ CAT.HEAD.FORM mv-or-pre-aux,
                                               CONT.HOOK.INDEX.E.ASPECT #asp ] ] > ],
                   CONT.HOOK.INDEX.E.ASPECT #asp ] ].
 
tam2-aux-lex := subj-raise-aux-no-pred &
  [ SYNSEM.LOCAL [ CAT [ HEAD [ FORM post-aux,
                                LEFTCOMP + ],
                         VAL.COMPS < [ OPT -,
                                       LOCAL [ CAT.HEAD.FORM any-form,
                                               CONT.HOOK.INDEX.E.ASPECT #asp ] ] > ],
                   CONT.HOOK.INDEX.E.ASPECT #asp ] ].
                   
epistemic-aux-lex := subj-raise-aux-with-pred &
  [ SYNSEM.LOCAL.CAT [ HEAD.FORM pre-aux,
                       VAL.COMPS < [ OPT -,
                                     LOCAL.CAT.HEAD.FORM mv-form ] > ] ].
    
pot-aux-lex := subj-raise-aux-with-pred &
  [ SYNSEM.LOCAL.CAT [ HEAD [ FORM sealed,
                              LEFTCOMP + ],
                       VAL.COMPS < [ OPT -,
                                     LOCAL.CAT.HEAD.FORM any-form ] > ] ].

;;;--------------------------------------------------------------------------
;;; Demonstrative determiners
;;; SPEC is non-empty, and already specified by basic-determiner-lex.
;;;
;;; 02-05-2009 gcs added determiner-lex
;;;--------------------------------------------------------------------------

demonstrative_a_rel := predsort.
proximal+dem_a_rel := demonstrative_a_rel. ; close to speaker
distal+dem_a_rel := demonstrative_a_rel.   ; away from speaker
mid+dem_a_rel := distal+dem_a_rel.         ; away, but not very far away
far+dem_a_rel := distal+dem_a_rel.         ; very far away
                                                             
base-determiner-lex := norm-hook-lex-item & basic-zero-arg &
    [ SYNSEM [ LOCAL [ CAT [ HEAD det,
                             VAL [ SPEC.FIRST.LOCAL.CONT.HOOK [ INDEX #ind,                                                               
                                                                LTOP #larg ],
                                   SPR < >,
                                   SUBJ < > ] ],
                       CONT [ HCONS < ! qeq & [ HARG #harg,
                                                LARG #larg ] ! >,
                              RELS.LIST.FIRST.PRED "exist_q_rel" ] ],
               LKEYS [ KEYREL quant-relation & [ ARG0 #ind,
                                                 RSTR #harg ] ] ] ].

demonst-determiner-lex := base-determiner-lex &
  [ SYNSEM [ LOCAL [ CAT [ HEAD.LEFTCOMP +,
                           VAL [ COMPS < [ LOCAL [ CAT.HEAD numcl & [ CLASSIF #cls ],
                                                   CONT.HOOK [ XARG #ind, 
                                                               LTOP #larg ] ] ] >,
                                 SPEC.FIRST.LOCAL [ CAT.HEAD.CLASSIF #cls,
                                                    CONT.HOOK [ INDEX #ind & 
                                                                      [ COG-ST activ+fam,
                                                                        PNG.GEND inanimate],
                                                                LTOP #larg ] ] ] ],
                     CONT.RELS < ! [ ] , #akr ! > ],
             LKEYS.ALTKEYREL #akr & arg1-ev-relation & [ LBL #larg,
                                                         ARG1 #ind ] ] ].

; 02-14-2009 gcs
; we interrupt your regularly scheduled determiners to bring you a special
; type for (bare or numbered) numerical classifiers selected by a demonstrative:

demonst-numcl-lex := raise-sem-lex-item &
    [ SYNSEM.LOCAL [ CAT [ HEAD numcl & [ MOD < > ],
                           VAL [ COMPS < [ OPT +, LOCAL [ CAT.HEAD num,
                                                          CONT.HOOK [ XARG #xarg, 
                                                                      LTOP #larg ] ] ] >,
                                 SPEC < >,
                                 SPR < >,
                                 SUBJ < > ] ],
                     CONT.HOOK [ XARG #xarg, LTOP #larg ] ] ].
                     
sg-demonst-numcl-lex := demonst-numcl-lex &                     
    [ STEM.FIRST #cls,
      SYNSEM.LOCAL.CAT [ HEAD.CLASSIF #cls,
                         VAL.COMPS < [ LOCAL.CONT.HOOK.XARG.PNG.NUM sg ] > ] ].

pl-demonst-numcl-lex := demonst-numcl-lex
    [ SYNSEM.LOCAL.CAT.VAL.COMPS < [ LOCAL.CONT.HOOK.XARG.PNG.NUM pl ] > ].

numcl-lex := base-determiner-lex &
    [ STEM.FIRST #cls,
      SYNSEM.LOCAL.CAT [ HEAD.LEFTCOMP #lc,
                         VAL [ COMPS < [ OPT -,
                                         LOCAL [ CAT.HEAD num & [ LEFTCOMP #lc ],
                                                 CONT.HOOK [ LTOP #larg,
                                                             XARG #ind ] ] ] >,
                               SPEC.FIRST.LOCAL [ CAT.HEAD.CLASSIF #cls,
                                                  CONT.HOOK [ LTOP #larg,
                                                              INDEX #ind ] ] ] ] ].
                                                            
number-name-relation := carg-relation & arg1-ev-relation &
    [ PRED "card_rel" ].

base-number-lex := single-rel-lex-item & norm-ltop-lex-item & no-hcons-lex-item &
    [ SYNSEM [ LOCAL [ CAT [ HEAD num & [ MOD < > ],
                             VAL [ SPR < >,
                                   SUBJ < >,
                                   COMPS < > ] ],
                       CONT.HOOK [ LTOP #larg, XARG #xar ] ],
               LKEYS.KEYREL number-name-relation & [ LBL #larg, ARG1 #xar ] ] ].

; digits 0-9 except 1
; (digit 1 inherits from base-number-lex which is underspecified for LEFTCOMP; 
; thus it can appear to the left or right of the classifier)
number-lex := base-number-lex & [ SYNSEM.LOCAL.CAT.HEAD.LEFTCOMP + ].

;;;--------------------------------------------------------------------------
;;; Complementizers and question particles
;;; We treat question particles as complementizers.
;;; Here is the lexical type for complementizers.
;;;--------------------------------------------------------------------------

comp-base-lex-item := raise-sem-lex-item & basic-one-arg &
  [ SYNSEM.LOCAL.CAT [ HEAD comp & [ MOD < > ],
                       VAL [ SPR < >,
                             SUBJ < >,
                             SPEC < >,
                             COMPS < #comp > ] ],
    ARG-ST < #comp &
             [ LOCAL.CAT [ MC +,
                           VAL [ SUBJ < >,
                                 COMPS < > ] ] ] > ].
                                 
complementizer-lex-item := comp-base-lex-item & [ SYNSEM.LOCAL.CAT.MC - ].

ques-complementizer-lex-item := complementizer-lex-item &
    [ SYNSEM.LOCAL [ CONT.HOOK.INDEX.SF ques,
                     CAT.HEAD.LEFTCOMP - ],
      ARG-ST < [ LOCAL.CAT [ HEAD comp ] ] > ].

prop-complementizer-lex-item := complementizer-lex-item &
    [ SYNSEM.LOCAL [ CONT.HOOK.INDEX.SF prop,
                     CAT.HEAD.LEFTCOMP - ],
      ARG-ST < [ LOCAL.CAT [ HEAD +vj ] ] > ].

qpart-lex-item := comp-base-lex-item &
  [ SYNSEM.LOCAL [ CAT [ HEAD.LEFTCOMP +, MC + ],
                   CONT.HOOK.INDEX.SF ques ],
    ARG-ST < [ LOCAL.CAT [ HEAD +vj ] ] > ].


;;;--------------------------------------------------------------------------
;;; Negators
;;; Type for negative adverbs.
;;;--------------------------------------------------------------------------

neg-adv-lex := basic-scopal-adverb-lex &
  [ SYNSEM.LOCAL.CAT [ VAL [ SPR < >,
                             COMPS < >,
                             SUBJ < > ],
                       POSTHEAD -,
                       HEAD.MOD < [ LOCAL.CAT.HEAD +vj,
                                    LIGHT + ] > ] ].


;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;;; Phrasal types
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

;Constraint on MC used to be part of matrix.tdl
;;it applies to all wo implementations, except for v2

basic-head-comp-phrase :+ [ SYNSEM.LOCAL.CAT.MC #mc,
    HEAD-DTR.SYNSEM.LOCAL.CAT.MC #mc ].

basic-head-mod-phrase-simple :+ [ SYNSEM.LOCAL.CAT.MC #mc,
    NON-HEAD-DTR.SYNSEM.LOCAL.CAT.MC #mc ].

subj-head-phrase := decl-head-subj-phrase & head-final &
  [ HEAD-DTR.SYNSEM.LOCAL.CAT.VAL.COMPS < > ].
  
; Rules for building NPs.  Note that the Matrix uses SPR for
; the specifier of nouns and SUBJ for the subject (specifier) of verbs.

; 02-13-2009 gcs Make sure selected determiner has its COMPS fulfilled
head-spec-phrase := basic-head-spec-phrase & head-initial &
  [ NON-HEAD-DTR.SYNSEM [ LOCAL.CAT.VAL.COMPS olist,
                          OPT - ] ].

; Bare NP phrase.

bare-np-phrase := basic-bare-np-phrase &
  [ C-CONT.RELS <! [ PRED "exist_q_rel" ] !> ].
  
; Head-Complement and Complement-Head

; 02-13-2009 gcs
; was [HEAD +nvjrpdmo] which is wrong because we need H-C for complementizer /waa/ 'that'
; could switch to +nvjrpcmo since we never need H-C for determiners

head-comp-phrase := basic-head-1st-comp-phrase & head-initial &
  [ SYNSEM.LOCAL.CAT [  MC #mc ],
    HEAD-DTR.SYNSEM.LOCAL.CAT [ HEAD.LEFTCOMP -, MC #mc ] ].
    
comp-head-phrase := basic-head-1st-comp-phrase & head-final &
  [ SYNSEM.LOCAL.CAT.VAL.SPEC #spec,
    HEAD-DTR.SYNSEM.LOCAL.CAT [ HEAD.LEFTCOMP +,
                                VAL.SPEC #spec ] ].

cd-comp-head-phrase := comp-head-phrase &
  [ SYNSEM.LOCAL.CAT.HEAD +cd ].
                                
v-comp-head-phrase := comp-head-phrase &
  [ SYNSEM.LOCAL.CAT.HEAD verb,
    HEAD-DTR.SYNSEM.LOCAL.CAT.HEAD.FORM post-aux ].
    
d-comp-head-phrase := comp-head-phrase &
  [ SYNSEM.LOCAL.CAT.HEAD verb,
    HEAD-DTR.SYNSEM.LOCAL.CAT.HEAD.FORM sealed ].

; This grammar includes head-modifier rules.  To keep
; out extraneous parses, constrain the value of MOD on
; various subtypes of head.  This may need to be loosened later.
; This constraint says that only adverbs, adjectives,
; and adpositions can be modifiers:

+nvcdmo :+ [ MOD < > ].

;;;--------------------------------------------------------------------------
;;; Coordination Strategy 1
;;;--------------------------------------------------------------------------

n1-top-coord-rule := basic-n-top-coord-rule & monopoly-top-coord-rule &
  [ SYNSEM.LOCAL.COORD-STRAT "1" ].

n1-mid-coord-rule := basic-n-mid-coord-rule & monopoly-mid-coord-rule &
  [ SYNSEM.LOCAL.COORD-STRAT "1" ].

n1-bottom-coord-rule := conj-first-bottom-coord-rule & n-bottom-coord-phrase &
  [ SYNSEM.LOCAL.COORD-STRAT "1" ].

;;; Coordination Strategy 1

np1-top-coord-rule := basic-np-top-coord-rule & monopoly-top-coord-rule &
  [ SYNSEM.LOCAL.COORD-STRAT "1" ].

np1-mid-coord-rule := basic-np-mid-coord-rule & monopoly-mid-coord-rule &
  [ SYNSEM.LOCAL.COORD-STRAT "1" ].

np1-bottom-coord-rule := conj-first-bottom-coord-rule & np-bottom-coord-phrase &
  [ SYNSEM.LOCAL.COORD-STRAT "1" ].

;;; Coordination Strategy 1

vp-coord-phrase :+ [ LCOORD-DTR.SYNSEM.LOCAL.CAT.HEAD.FORM mv-form,
                     RCOORD-DTR.SYNSEM.LOCAL.CAT.HEAD.FORM mv-form ].

vp1-top-coord-rule := basic-vp-top-coord-rule & monopoly-top-coord-rule &
  [ SYNSEM.LOCAL.COORD-STRAT "1" ].

vp1-mid-coord-rule := basic-vp-mid-coord-rule & monopoly-mid-coord-rule &
  [ SYNSEM.LOCAL.COORD-STRAT "1" ].

vp1-bottom-coord-rule := conj-first-bottom-coord-rule & vp-bottom-coord-phrase &
  [ SYNSEM.LOCAL.COORD-STRAT "1",
    NONCONJ-DTR.SYNSEM.LOCAL.CAT.HEAD.FORM mv-form ].

;;; Coordination Strategy 1

s1-top-coord-rule := basic-s-top-coord-rule & monopoly-top-coord-rule &
  [ SYNSEM.LOCAL.COORD-STRAT "1" ].

s1-mid-coord-rule := basic-s-mid-coord-rule & monopoly-mid-coord-rule &
  [ SYNSEM.LOCAL.COORD-STRAT "1" ].

s1-bottom-coord-rule := conj-first-bottom-coord-rule & s-bottom-coord-phrase &
  [ SYNSEM.LOCAL.COORD-STRAT "1" ].

;;;--------------------------------------------------------------------------
;;; Coordination Strategy 2
;;;--------------------------------------------------------------------------

vp2-top-coord-rule := basic-vp-top-coord-rule & apoly-top-coord-rule &
  [ SYNSEM.LOCAL.COORD-STRAT "2" ].

vp2-bottom-coord-rule := unary-bottom-coord-rule & vp-bottom-coord-phrase &
  [ SYNSEM.LOCAL [ COORD-STRAT "2",
                   COORD-REL.PRED "_and_coord_rel" ],
    NONCONJ-DTR.SYNSEM.LOCAL.CAT.HEAD.FORM mv-form ].