DEMO   ENGLISH   CONFIG (1.0)
  ROOTCAT   ROOT.
  FILES  MCONFIG.lfg 
  	 morph-lex-10.lfg  "for lexical entries for tags from FST"
	 morph-rules-10.lfg "for sublexical rules".
  LEXENTRIES   (DEMO ENGLISH) (MORPH ENGLISH).
  TEMPLATES (DEMO ENGLISH). 
  RULES   (DEMO ENGLISH) (MORPH ENGLISH).
  MORPHOLOGY (DEMO ENGLISH).
  GOVERNABLERELATIONS    SUBJ OBJ OBJ2 COMP XCOMP OBL OBL-?+.
  SEMANTICFUNCTIONS    ADJUNCT  TOPIC FOCUS STANDARD.
  NONDISTRIBUTIVES    NUM PERS CONJ-FORM.
  EPSILON   e.
OPTIMALITYORDER NOGOOD  subj-contr PPadj +PPattach.
GENOPTIMALITYORDER NOGOOD .

----

DEMO   ENGLISH   RULES (1.0)

   ROOT --> { { S " have other things here as well, imperatives, etc." 
 	    | Stop } "topicalized sentence" 
 	    (PERIOD)
 	  | Simp "or an imperative"
 	    EXCL: (^ STMT-TYPE) = imperative }. 

   Simp --> e: (^ SUBJ PRED) = 'pro' "empty subject for imperative"
	       (^ SUBJ PERS) = 2 ;
	  VP. 	     

   Stop --> NP: (^ TOPIC) = ! "things here are topics"
		(^ {XCOMP|COMP}* {OBJ|OBJ2}) = !; "functional uncertainty path"
 	  (COMMA) "optional comma followed by the rest of sentence"
 	  S.  

   S --> NP: (^ SUBJ)=!
	     (! CASE)=NOM;
 	 VP: ^=!. 

   CP --> C S.				

   VP --> "this rule is awkward, could find a better way via metacategories"
	  (AUX)
 	  V: ^=!; 
 	  (NP: (^ OBJ)=! "either direct object"
	       (! CASE)=ACC) 
 	  (NP: (^ OBJ2)=! "secondary object"
	       (! CASE)=DAT)
 	  PP*: { ! $ (^ ADJUNCT) 
		 (! PTYPE) =c sem "only semantic Ps here"
		 @(OT-MARK PPadj) "disprefer adjunct PPs" 
	       | (^ OBL) = !}; 
 	  (PP: (^ OBL-TO) = !
	       "example of a constraining equation: require a value with =c"
	       (! PFORM) =c to)
 	  (PP: (^ OBL-AG) = ! 
	       "example of a constraining equation: require a value with =c"
	       (! PFORM) =c by )
 	  ADV*: ! $ (^ ADJUNCT);
 	  ( { CP: (^ COMP) = ! "or a CP"
 	   | "or an XCOMP"
 	     VPinf: (^ XCOMP) = !}).

   VPinf --> PARTinf VP.   "for embedded to phrases"

   NP --> { "either a full NP"
 	    (DP)
 	    AP*: ! $ (^ ADJUNCT); 
 	    N
 	    PP*: ! $ (^ ADJUNCT) 
		 (! PTYPE) =c sem
		 @(OT-MARK PPattach); "prefer PPs attached to NPs"
 	  | "or a personal pronoun"
 	    PRON: ^=! 
		  (! PRON-TYPE) = pers}.			

   DP = "example of a metacategory"
{ "either a determiner"
 	  D 
 	| "or a possesive pronoun"
 	  PRON: (^ SPEC POSS ) = ! 
		(! PRON-TYPE) =c poss}. 

   AP --> ADV*: ! $ (^ ADJUNCT);
 	  Adj
 	  (COMMA).						

   PP --> { P: ^ = ! "head of semantic PP"
	       (! PTYPE) =c sem; 
 	    NP: (^ OBJ) = !
	   |P: ^ = ! "head of non-semantic PP"
	       (! PTYPE) =c nosem; 
 	    NP: ^ = !} . 

----
DEMO   ENGLISH   TEMPLATES (1.0)

 OT-MARK(_mark) = "assigns an OT mark, from common templates"
       _mark $ o::*.

   OPT-TRANS(P) = "template for verbs that can be trans or intrans"
	  { @(TRANS P) 
	  | @(INTRANS P) }. 
	  
 INTRANS(P) = (^ PRED) = 'P<(^SUBJ)>'.

 INTRANS-OBL(P) = (^ PRED) = 'P<(^SUBJ)(^OBL)>'.

"new TRANS Template allowing Passive Lexical Rule"

TRANS(P) = @(PASS (^ PRED)='P<(^ SUBJ) (^ OBJ)>').


   COMP-OBJ(P) = "think, say"
	  { (^ PRED) = 'P<(^SUBJ)(^COMP)>' 
	  | @(TRANS P)}. 

SUBJ-TRANS-CONTR(P) = "promise -- subject control verb"
			       (^PRED) = 'P<(^SUBJ)(^OBJ)(^XCOMP)>'
			       (^ XCOMP SUBJ) = (^ SUBJ).


OBJ-TRANS-CONTR(P) = "persuade -- object control verb"
				(^PRED) = 'P<(^SUBJ)(^OBJ)(^XCOMP)>'
				(^ XCOMP SUBJ) = (^ OBJ).

SUBJ-OBJ-CONTR(P) = "for want"
			 { (^ PRED) = 'P<(^SUBJ)(^XCOMP)>'
			   (^ XCOMP SUBJ) = (^ SUBJ) 
			 | @(OBJ-TRANS-CONTR P)
                           @(OT-MARK subj-contr)}.

   SUBJ-RAISE(P) = "Raising"
	  (^ PRED) = 'P<(^XCOMP)>(^SUBJ)' 
	  (^ XCOMP SUBJ) = (^ SUBJ). 
	  
 "new DITRANS template, allowing Dative Shift and Passive"
	  
	  DITRANS (P) = @(PASS @(DAT-SHIFT (^ PRED)='P<(^ SUBJ) (^ OBJ) (^ OBL-TO)>')).

DITRANS-OBL(P) = @(PASS (^ PRED)='P<(^ SUBJ) (^ OBJ) (^ OBL)>').

   PASS(SCHEMATA) = { SCHEMATA 
	   |SCHEMATA 
	    (^ PASSIVE) = +
	    (^ PARTICIPLE)=c past
	    (^ OBJ)-->(^ SUBJ)
	    (^ OBJ2) --> (^ OBJ)  "for dative shift"
	    { (^ SUBJ)-->(^ OBL-AG)
	     |(^ SUBJ)-->NULL}}.

DAT-SHIFT(SCHEMATA) = { SCHEMATA 
	   |SCHEMATA 
	    (^ OBJ)-->(^ OBJ2)
	    (^ OBL-TO)-->(^ OBJ)}. 


VPROG =     (^ ASPECT PROG) = +.

   VPRES = @(TENSE pres) 
	   @(MOOD indicative). 

   VPAST = @(TENSE past) 
	  @(MOOD indicative). 

   PASTP = (^ PARTICIPLE) = past
	  "require tense from auxiliary via existential constraint"
	  (^ TENSE). 

   BARE-AGR = { (^ SUBJ NUM) = pl "either it is plural"
	  | (^ SUBJ PERS) ~= 3 "or singular and not 3rd person"
	    (^ SUBJ NUM) = sg}.

   S-AGR = (^ SUBJ PERS) = 3  "for verbs in -s"
	  (^ SUBJ NUM) = sg. 


   NUM(N) = (^ NUM) = N.

	
   PREP(P) = { (^ PRED) = 'P<(^OBJ)>' 
	    (^ PTYPE) = sem
	  | (^ PTYPE) = nosem
	    (^ PFORM) = P}.
  
   TENSE(T) = (^ TENSE) = T.  

   MOOD(M) = (^ MOOD) = M.

   PRED(P) = (^ PRED) = 'P'. 

  
"old template, reorganized due to integration of morphology"
" COUNT-NOUN(P N) = @(PRED P)
	  (^ NUM) = N
	  (^ PERS) = 3
	  (^ NTYPE) = count. "

"template for pronouns of all types" 

   PRON(P Z N T) = (^ PRED) = 'P'
	  (^ NUM) = N
	  (^ PERS) = Z
	  (^ PRON-TYPE) = T
	  (^ NTYPE) = pron. 

"template for ntype"

NTYPE(N) =  (^ NTYPE) = N.


----

DEMO ENGLISH LEXICON (1.0)


"all morphology entries for verbs here:"			 

dog 	  +V-S XLE "this notation allows a noun reading from -unknown 
	       	   in morph-lex as well"
		   @(TRANS dog); 
	  ETC.

devour	  V-S XLE @(TRANS %stem).

drink	  V-S XLE @(OPT-TRANS %stem).

eat	  V-S XLE @(OPT-TRANS %stem).

educate	  V-S XLE @(TRANS %stem).

give	  V-S XLE @(DITRANS %stem).

like 	  V-S XLE "using the morphological analyzer"
		  "either a transitive or a subj control" 
                  "use the %stem possibility for better generalization"
		  "{ @(TRANS like) | @(SUBJ-TRANS-CONTR P)}."
		  { @(TRANS %stem) | @(SUBJ-TRANS-CONTR %stem)}.

persuade  V-S XLE @(OBJ-TRANS-CONTR %stem).

promise	  V-S XLE @(SUBJ-TRANS-CONTR %stem).

put	  V-S XLE @(DITRANS-OBL %stem)
	      	   (^ OBL PTYPE) =c sem.

rain	  V-S XLE @(INTRANS %stem).

say	  V-S XLE @(COMP-OBJ %stem).

seem	  V-S XLE @(SUBJ-RAISE %stem).

sleep	  V-S XLE @(INTRANS %stem).

steal	  V-S XLE @(TRANS %stem).

step	  V-S XLE @(INTRANS-OBL %stem).

think	  V-S XLE @(COMP-OBJ %stem).

wait	  V-S XLE {@(INTRANS %stem)|
	      	   @(INTRANS-OBL %stem)
		   (^ OBL PFORM) =c on}.

want	  V-S XLE @(SUBJ-OBJ-CONTR %stem).


"prepositions"
			 
by P * @(PREP by). 

to 	  P * @(PREP to);
	  PARTinf * .  "for infinitives, could specify some more info if wanted to"

on 	  P * @(PREP on). 

in 	  P * @(PREP in). 

over 	  P * @(PREP over).

"adverbs"

quickly   ADV * @(PRED quickly). 

very   ADV * @(PRED very). 


"auxiliaries"

was 	  AUX * @(TENSE past)
		@S-AGR
		(^ AUX-FORM) = be. "possible way of killing overgeneration"
	

is 	  AUX * @(TENSE pres)
		@S-AGR
		(^ AUX-FORM) = be. "possible way of killing overgeneration"


be 	  AUX * @(TENSE pres)
		@S-AGR
		(^ AUX-FORM) = be.

"complementizers"

that 	  C * (^ COMP-FORM) = that
	      (^ CLAUSE-TYPE) = declarative.


"determiners here"

the  D *  (^DEF) = +.

The  D *  (^DEF) = +.

a  D *  (^DEF) = -
        (^ NUM) = sg.

A  D *  (^DEF) = -
        (^ NUM) = sg.


"pronouns"

I	PRON * @(PRON I 1 sg pers).

me	PRON * @(PRON me 1 sg pers).

You	PRON * {@(PRON you 2 sg pers)
	       |@(PRON you 2 pl pers)}.

He	PRON * @(PRON he 3 sg pers).

She	PRON * @(PRON she 3 sg pers).

We	PRON * @(PRON we 1 pl pers).

They	PRON * @(PRON they 3 pl pers). 

My	PRON * @(PRON my 1 sg poss). 

my	PRON * @(PRON my 1 sg poss).

Her	PRON * @(PRON her 3 sg poss).

It	PRON * @(PRON it 3 sg pers).


"punctuation"

.  PERIOD  * (^ STMT-TYPE) = declarative.

,  COMMA * . 

!  EXCL * (^ STMT-TYPE) = imperative. 

?  QM * (^ STMT-TYPE) = interrogative. 


----