DEMO   ENGLISH   CONFIG (1.0)
  ROOTCAT   ROOT.
  FILES  MCONFIG.lfg .
  LEXENTRIES   (DEMO ENGLISH).
  TEMPLATES (DEMO ENGLISH). 
  RULES   (DEMO 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  PPadj +PPattach.
GENOPTIMALITYORDER NOGOOD .

----

DEMO   ENGLISH   RULES (1.0)

   ROOT --> S    "can have other things here as well, imperatives, etc." 
 	  (PERIOD).

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

   CP --> C S. 

   VP --> (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"
	    "the next bit is an optional disjunction --- not ideal"
 	    ({ "either a determiner"
 	       D 
 	     | "or a possesive pronoun"
 	       PRON: (^ SPEC POSS ) = ! 
		     (! PRON-TYPE) =c poss})
 	    AP*: ! $ (^ ADJUNCT); 
 	    N
 	    PP*: ! $ (^ ADJUNCT) 
		 (! PTYPE) =c sem
		 @(OT-MARK PPattach); "prefer PPs attached to NPs"
 	  | "or a personal pronoun"
 	    PRON: ^=! 
		  (! PRON-TYPE) = pers}.			

   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)}.

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

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)}. 


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

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

   PASTP = (^ PARTICIPLE) = past. 

   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. 
	
   PREP(P) = { (^ PRED) = 'P<(^OBJ)>' 
	    (^ PTYPE) = sem
	  | (^ PTYPE) = nosem
	    (^ PFORM) = P}.

  
   TENSE(T) = (^ TENSE) = T.  

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

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

   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 names"

NAME(P) = @(PRED P)
	  (^ NUM) = sg
	  (^ PERS) = 3
	  (^ NTYPE) = name.

----

DEMO ENGLISH LEXICON (1.0)

"all names here"

John N * @(NAME John).

Mary N * @(NAME Mary).

Bill N * @(NAME Bill).

Kim N * @(NAME Kim).

"all nouns here"

beans 	  N * @(COUNT-NOUN beans pl).

cat 	  N * @(COUNT-NOUN cat sg).

yoghurt   N * @(COUNT-NOUN yoghurt sg).

cage 	  N * @(COUNT-NOUN cage sg).

girl 	  N * @(COUNT-NOUN girl sg).

boy 	  N * @(COUNT-NOUN boy sg).

bench 	  N * @(COUNT-NOUN bench sg).

bone 	  N * @(COUNT-NOUN bone sg).

bones 	  N * @(COUNT-NOUN bone pl).

"bones 	  N * (^ PRED) = 'bone'
	      (^ NUM) = pl
	      (^ PERS) = 3. "

homework  N * @(COUNT-NOUN homework sg).

zookeeper N *  @(COUNT-NOUN zookeeper sg).

gorilla	  N *  @(COUNT-NOUN gorilla sg).

gorillas  N *  @(COUNT-NOUN gorilla pl).

banana	  N *  @(COUNT-NOUN banana sg).

bananas	  N *  @(COUNT-NOUN banana pl).

dog 	  N *  @(COUNT-NOUN dog sg).

dogs 	  N *  @(COUNT-NOUN dog pl);
	  V *  @(TRANS dog) 
	       @VPRES
               @S-AGR.

garden 	  N *  @(COUNT-NOUN garden sg).

"all adjectives here"

small	Adj * @(PRED small). 

black	Adj * @(PRED black). 

hungry	Adj * @(PRED hungry). 

smart	Adj * @(PRED smart). 

"all verbs here"

walk 	  V * @(INTRANS walk)
	      @VPRES
	      @BARE-AGR;
	  N * @(COUNT-NOUN walk sg).

"do NOT have duplicate headwords/lexical entries!!!" 
"walk      N * @(COUNT-NOUN walk sg)." 

	      
ate 	  V * @(OPT-TRANS eat) "optionally transitive verbs"
	      @VPAST.

eats 	  V * @(OPT-TRANS eat)
	      @VPRES
              @S-AGR. 

eat 	  V * @(OPT-TRANS eat).

drinks   V * @(OPT-TRANS drink)
             @VPRES
             @S-AGR. 

devour 	  V * @(TRANS devour) 
              "don't do this, do Lexical Rules instead"
	      "{ (^ PRED) = 'devour<(^SUBJ)(^OBJ)>' | 
		(^ PRED) = 'devour<(^OBJ)(^OBL)>' }"
	      @VPRES
	      @BARE-AGR. 

devours  V * @(TRANS devour) 
	     @VPRES
             @S-AGR.

devoured  V * @(TRANS devour) 
              @VPAST
              @PASTP. 

put 	  V * @(DITRANS-OBL put)
	      (^ OBL PTYPE) =c sem
	      @VPAST
	      @PASTP.

gave 	  V * @(DITRANS give)
	      @VPAST. 

gives     V * @(DITRANS give)
	      @VPRES
	      @S-AGR.

given     V * @(DITRANS give)
	      @VPAST
	      @PASTP.

sleeps 	  V * @(INTRANS sleep)
	      @VPRES
              @S-AGR. 

sleep 	  V * @(INTRANS sleep)
              @VPRES
              @BARE-AGR.

slept 	  V * @(INTRANS sleep)
	      @VPAST
	      @PASTP.

waited 	  V * { @(INTRANS wait) |
		@(INTRANS-OBL wait)
		(^ OBL PFORM) =c on
	      }
	      @VPAST
	      @PASTP. 

steps	  N * @(COUNT-NOUN step pl);
	  V * @(INTRANS-OBL step)			"2 solutions -> a1 (sem. P) right one"
	      @VPRES
              @S-AGR.	      

think 	  V * @(COMP-OBJ think)		     
	      @VPRES.

thought   V * @(COMP-OBJ think)
	      @VPAST
	      @PASTP.


said 	  V * @(COMP-OBJ say)
	      @VPAST
	      @PASTP.

wants 	  V * @(SUBJ-OBJ-CONTR P)
	      @VPRES
	      @S-AGR.

want	  V * @(SUBJ-OBJ-CONTR P)
	      @VPRES.

wanted	  V * @(SUBJ-OBJ-CONTR P)
	      @VPAST
	      @PASTP.

persuaded V * @(OBJ-TRANS-CONTR P)
	      @VPAST
	      @PASTP.

promised  V * @(SUBJ-TRANS-CONTR P)
	      @VPAST
	      @PASTP.
			 
			 
			 
"prepositions"
			 
by P * @(PREP by). 

to 	  P * (^ PFORM) = to
	      (^ PTYPE) = nosem;
	  PARTinf * .  "could specify some 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"
		"(^ PARTICIPLE) ~= past". 

"complementizers"

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


"determiners here"

the  D *  (^DEF) = +.

The  D *  (^DEF) = +.

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


"pronouns"

I	PRON * @(PRON I 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).


"punctuation"

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

,  COMMA * . 

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

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


----