14
15
16:- module(sentence_failure, [
17 get_all_sentence_errors/2, 18 get_sentence_error_text/2 19 ]). 20
21:- use_module('../lexicon/lexicon_interface'). 22
23:- use_module('../lexicon/chars', [
24 is_capitalized/1
25 ]). 26
27:- use_module('../lexicon/is_in_lexicon', [
28 is_functionword/1
29 ]). 30
31:- use_module('../lexicon/illegalwords'). 32
33:- style_check(-singleton). 34:- style_check(-discontiguous). 35:- use_module('grammar.plp'). 36:- style_check(+discontiguous). 37:- style_check(+singleton).
52get_all_sentence_errors(SentenceTokens, ErrorTextList) :-
53 findall(ErrorText, get_sentence_error_text(SentenceTokens, ErrorText), ErrorTextListIntermediate),
54 55 list_to_set(ErrorTextListIntermediate, ErrorTextList).
65get_sentence_error_text(SentenceTokens, ErrorText) :-
66 member(IllegalWord, SentenceTokens),
67 68 69 is_illegalword(IllegalWord, ErrorText).
70
72get_sentence_error_text(SentenceTokens, ErrorText) :-
73 append(_, [Token, '<>', Token|_], SentenceTokens),
74 \+ is_repeatable(Token),
75 with_output_to(atom(ErrorText), format("Token \'~w\' repeated.", [Token])).
76
78get_sentence_error_text(SentenceTokens, ErrorText) :-
79 append(_, [There, is, Token, '<>' | _], SentenceTokens),
80 (
81 There = there
82 ;
83 There = 'There'
84 ),
85 (
86 Token = the
87 ;
88 is_capitalized(Token)
89 ;
90 pn_sg(Token, _, _)
91 ),
92 with_output_to(atom(ErrorText), format("The construct \'there is\' + \'~w\' is not allowed.", [Token])).
93
95get_sentence_error_text(SentenceTokens, ErrorText) :-
96 append(_, [There, are, Token, '<>' | _], SentenceTokens),
97 (
98 There = there
99 ;
100 There = 'There'
101 ),
102 (
103 Token = the
104 ;
105 is_capitalized(Token)
106 ;
107 pn_pl(Token, _, _)
108 ),
109 with_output_to(atom(ErrorText), format("The construct \'there are\' + \'~w\' is not allowed.", [Token])).
110
113get_sentence_error_text(SentenceTokens, ErrorText) :-
114 append(_, [Wordform, '<>', that | _], SentenceTokens),
115 (
116 iv_finsg(Wordform, Verb)
117 ;
118 iv_infpl(Wordform, Verb)
119 ),
120 with_output_to(atom(ErrorText), format("The intransitive verb \'~w\' cannot be followed by that-subordination. Use a transitive verb.", [Verb])).
121
122get_sentence_error_text(SentenceTokens, 'The sentence contains \'then\' but not \'if\'.') :-
123 member(then, SentenceTokens),
124 \+ member(if, SentenceTokens),
125 \+ member('If', SentenceTokens).
126
127get_sentence_error_text(SentenceTokens, 'The sentence contains \'if\' but not \'then\'.') :-
128 (
129 member(if, SentenceTokens)
130 ;
131 member('If', SentenceTokens)
132 ),
133 \+ member(then, SentenceTokens).
134
135
141get_sentence_error_text(SentenceTokens, 'Commas must be immediately followed by \'and\' or \'or\', or must occur at specified positions in lists, sets and commands.') :-
142 append(Front, [',', NextToken | Tail], SentenceTokens),
143 144 NextToken \= and,
145 146 NextToken \= or,
147 148 \+ member('!', Tail),
149 150 \+ (member('[', Front), member(']', Tail)),
151 152 \+ (member('{', Front), member('}', Tail)).
153
154
155get_sentence_error_text(_, 'This is the first sentence that was not ACE. The sign <> indicates the position where parsing failed.').
164is_repeatable('{').
165is_repeatable('}').
166is_repeatable('(').
167is_repeatable(')').
168is_repeatable('[').
169is_repeatable(']').
170is_repeatable('"')
Sentence Failure