2:- module(tense,
3 [ tense/4, 4 aspect/5 5 ]). 6
7:- use_module(semlib(options),[option/2]). 8:- use_module(library(lists),[member/2]). 9:- use_module(boxer(categories),[att/3]). 10
11
15
16tense(Mood,Index,Att-[sem:Tag|Att],Sem):-
17 option('--tense',true),
18 member(Mood,[dcl,inv,wq,q]),
19 att(Att,pos,PoS),
20 pos2tense(PoS,Index,Sem,Tag), !.
21
22tense(com,_,Att-[sem:'MOR'|Att],Sem):- !,
23 Sem = lam(S,lam(M,app(S,M))).
24
25tense(adj,_,Att-[sem:'IST'|Att],Sem):- !,
26 Sem = lam(S,lam(M,app(S,M))).
27
28tense(ng,_,Att-[sem:'EXG'|Att],Sem):-
29 Sem = lam(S,lam(M,app(S,M))).
30
31tense(pt,_,Att-[sem:'EXT'|Att],Sem):-
32 Sem = lam(S,lam(M,app(S,M))).
33
34tense(pss,_,Att-[sem:'EXV'|Att],Sem):-
35 Sem = lam(S,lam(M,app(S,M))).
36
37tense(_,_,Att-[sem:'EXS'|Att],Sem):-
38 Sem = lam(S,lam(M,app(S,M))).
39
40
44
45pos2tense('VBD',Index,Sem,'PST'):-
46 Sem = lam(S,lam(F,app(S,lam(E,merge(B2:drs([B1:[]:N,B2:Index:T],
47 [B1:[]:pred(N,now,a,1),
48 B2:[]:rel(E,T,temp_included,1),
49 B2:[]:rel(T,N,temp_before,1)]),
50 app(F,E)))))).
51
52
56
57pos2tense(Cat,Index,Sem,'NOW'):-
58 member(Cat,['VBP','VBZ']), !,
59 Sem = lam(S,lam(F,app(S,lam(E,merge(B2:drs([B1:[]:N,B2:Index:T],
60 [B1:[]:pred(N,now,a,1),
61 B2:[]:rel(E,T,temp_included,1),
62 B2:[]:eq(T,N)]),
63 app(F,E)))))).
64
65
69
70pos2tense('MD',Index,Sem,'FUT'):-
71 Sem = lam(S,lam(F,app(S,lam(E,merge(B2:drs([B1:[]:N,B2:Index:T],
72 [B1:[]:pred(N,now,a,1),
73 B2:[]:rel(E,T,temp_included,1),
74 B2:[]:rel(N,T,temp_before,1)]),
75 app(F,E)))))).
76
77
81
85
86aspect(pt,_,Index,Att-[sem:'ENT'|Att],Sem):-
87 option('--tense',true),
88 att(Att,pos,PoS),
89 member(PoS,['VBZ','VBP']), !,
90 Sem = lam(S,lam(F,app(S,lam(E,merge(B2:drs([B1:[]:N,B2:Index:T,B2:[]:St],
91 [B1:[]:pred(N,now,a,1),
92 B2:[]:eq(T,N),
93 B2:[]:rel(St,T,temp_includes,1),
94 B2:[]:rel(E,St,temp_abut,1)]),
96 app(F,E)))))).
97
98
102
103aspect(pt,_,Index,Att-[sem:'EPT'|Att],Sem):-
104 option('--tense',true),
105 att(Att,pos,'VBD'),
106 Sem = lam(S,lam(F,app(S,lam(E,merge(B2:drs([B1:[]:N,B2:Index:T,B2:[]:St],
107 [B1:[]:pred(N,now,a,1),
108 B2:[]:rel(T,N,temp_before,1),
109 B2:[]:rel(St,T,temp_includes,1),
110 B2:[]:rel(E,St,temp_abut,1)]),
112 app(F,E)))))).
113
117
118aspect(pt,Mood,Index,Att1-[sem:'EXT'|Att2],Sem):-
119 option('--tense',true), !,
120 tense(Mood,Index,Att1-Att2,Sem).
121
122
126
127aspect(pss,pt,Index,Att-[sem:'ETV'|Att],Sem):-
128 option('--tense',true), !,
129 Sem = lam(S,lam(F,app(S,lam(E,merge(B2:drs([B2:Index:T,B2:[]:St],
130 [B2:[]:rel(St,T,temp_includes,1),
131 B2:[]:rel(E,St,temp_overlap,1)]),
133 app(F,E)))))).
134
135
139
140aspect(ng,pt,Index,Att-[sem:'ETG'|Att],Sem):-
141 option('--tense',true), !,
142 Sem = lam(S,lam(F,app(S,lam(E,merge(B2:drs([B2:Index:T,B2:[]:St],
143 [B2:[]:rel(St,T,temp_includes,1),
144 B2:[]:rel(E,St,temp_overlap,1)]),
146 app(F,E)))))).
147
148
152
153aspect(ng,_,Index,Att-[sem:'ENG'|Att],Sem):-
154 option('--tense',true),
155 att(Att,pos,PoS),
156 member(PoS,['VBZ','VBP']), !,
157 Sem = lam(S,lam(F,app(S,lam(E,merge(B2:drs([B1:[]:N,B2:Index:T,B2:[]:St],
158 [B1:[]:pred(N,now,a,1),
159 B2:[]:eq(T,N),
160 B2:[]:rel(St,T,temp_includes,1),
161 B2:[]:rel(E,St,temp_overlap,1)]),
163 app(F,E)))))).
164
165
169
170aspect(ng,_,Index,Att-[sem:'EPG'|Att],Sem):-
171 att(Att,pos,'VBD'),
172 option('--tense',true), !,
173 Sem = lam(S,lam(F,app(S,lam(E,merge(B2:drs([B1:[]:N,B2:Index:T,B2:[]:St],
174 [B1:[]:pred(N,now,a,1),
175 B2:[]:rel(T,N,temp_before,1),
176 B2:[]:rel(St,T,temp_included,1),
177 B2:[]:rel(E,St,temp_overlap,1)]),
179 app(F,E)))))).
180
184
185aspect(ng,Mood,Index,Att1-[sem:'EXG'|Att2],Sem):-
186 option('--tense',true), !,
187 tense(Mood,Index,Att1-Att2,Sem).
188
189
193
194aspect(_,Mood,Index,Att,Sem):-
195 tense(Mood,Index,Att,Sem)