DEMO   ENGLISH   CONFIG (1.0)
  ROOTCAT   S.
  FILES  .
  LEXENTRIES   (DEMO ENGLISH).
  TEMPLATES (DEMO ENGLISH). 
  RULES   (DEMO ENGLISH).
  MORPHOLOGY (DEMO ENGLISH).
  GOVERNABLERELATIONS    SUBJ OBJ OBJ2 COMP XCOMP OBL OBL-?+.
  SEMANTICFUNCTIONS    ADJUNCT  TOPIC FOCUS POSS STANDARD.
  NONDISTRIBUTIVES    NUM PERS CONJ-FORM.
  EPSILON   e.
  OPTIMALITYORDER NOGOOD  PPadj +PPattach.
  GENOPTIMALITYORDER NOGOOD .

----

DEMO ENGLISH MORPHOLOGY (1.0)

TOKENIZE:
P!basic-parse-tok.fst G!default-gen-tokenizer.fst

----

DEMO   ENGLISH   RULES (1.0)

   S --> NP: (^ SUBJ)=!
	     (! CASE)=nom;
 	 VP
	 (PERIOD).  "for punctuation, optional for now"


   VP --> (AUX) "auxiliary introduced for passive" 
 	  V: ^=!;   "head of VP"
 	  (NP: (^ OBJ)=! "direct object"
	       (! CASE)=acc)
 	  (NP: (^ OBJ2) = !) "secondary object"
 	  PP*: { ! $ (^ ADJUNCT) "PPs can be all types of adjuncts"
		 (! PTYPE) =c sem "only semantic PPs here"
		 @(OT-MARK PPadj) "disprefer adjunct PPs" 
	       | (^ OBL) = ! "or a a general oblique"
	       };
 	  (PP: (^ OBL-TO) = ! "special obl for ditransitives"
	       "example of a constraining equation: require a value with =c"
	       (! PFORM) =c to)
 	  (PP: (^ OBL-AG) = ! "oblique agent of passive" 
	       "example of a constraining equation: require a value with =c"
	       (! PFORM) =c by ). 

   NP --> (D)  "optional determiner"
 	  AP*: ! $ (^ ADJUNCT); "introducing adjectives in sets"
 	  N   "head of NP"
 	  PP*: ! $ (^ ADJUNCT)  "PPs modifying NPs" 
	       (! PTYPE) =c sem   "have to be semantic" 
	       @(OT-MARK PPattach) "prefer PPs attached to NPs".
 

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

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



----
DEMO   ENGLISH   TEMPLATES (1.0)

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

   PASS(FRAME) = { FRAME "no passive, just give back subcat frame"
	          (^ PASSIVE) = - "no passive"
	  | FRAME "passive"
	    (^ PASSIVE) = + "mark as such"
	    (^ PARTICIPLE) =c past "make sure to have a past participle"
	    (^ OBJ)-->(^ SUBJ) "obj goes to subj"
	    { (^ SUBJ)-->(^ OBL-AG) "either make subj obl-ag"
	    | (^ SUBJ)--> NULL "or delete"
	    }
	  }. 

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

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


 "transitives can passivize"

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

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

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


   OPT-TRANS(P) = { (^ PRED) = 'P<(^SUBJ)(^OBJ)>'   "P is a variable"
	          | (^ PRED) = 'P<(^SUBJ)>' }.  "this template takes one argument:  P"
	  
   TENSE(T) = (^ TENSE) = T.  "the more general case"

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

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

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

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

   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. 

 COUNT-NOUN(P N) = @(PRED P)
	             (^ NUM) = N
	             (^ PERS) = 3
	             (^ NTYPE) = count. 

   PREP(P) = "template for most prepositions"
	  { (^ PRED) = 'P<(^OBJ)>' 
	    (^ PTYPE) = sem
	  | (^ PTYPE) = nosem
	    (^ PFORM) = P}.


 DEF =  (^ DEF). 

----

DEMO ENGLISH LEXICON (1.0)

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

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

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

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

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

dogs 	  N *  @(COUNT-NOUN dog pl).

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

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

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

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

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

"all verbs here"

saw	  V * @(TRANS see) "optionally transitive verbs"
	      @VPAST.

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

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

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


gave 	  V * @(DITRANS give)
	      @VPAST. 

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

given 	  V * @(DITRANS give)
	      { @VPAST | @PASTP}. 


appears   V * @(INTRANS appear)
	      @VPRES
	      @S-AGR.

appeared  V * @(INTRANS appear)
	      @VPAST. 

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

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

slept 	  V * @(INTRANS sleep)
	      @VPAST. 

waited 	  V * { @(INTRANS wait) | 
		@(INTRANS-OBL wait) 
		"this is the non-semantic OBL wait on a customer use"
		(^ OBL PFORM) =c on
		(^ PSEM) =c nosem }
	      @VPAST. 

"adjectives"

small	A * @(PRED small). 

smart	A * @(PRED smart). 

grey	A * @(PRED grey). 

"adverbs"

quickly   ADV * @(PRED quickly). 

very   ADV * @(PRED very). 

"prepositions"


by 	  P * @(PREP by). 

to 	  P *  @(PREP to).

on 	  P * @(PREP on). 

in 	  P * @(PREP in). 

with 	  P * @(PREP with). 


"auxiliaries"

was 	  AUX * @(TENSE past)
		{ (^ SUBJ PERS) = 1
                | (^ SUBJ PERS) = 3
                }
                (^ SUBJ NUM) = sg. 

"determiners"

the  D *  (^DEF) = +.

The  D *  (^DEF) = +.


a  D *  (^ DEF) = -   "this indefinite only marks singulars" 
        (^ NUM) = sg.


"punctuation"


. PERIOD * . 

, COMMA  * . 


----