1% This file is part of the Attempto Parsing Engine (APE).
    2% Copyright 2008-2013, Attempto Group, University of Zurich (see http://attempto.ifi.uzh.ch).
    3%
    4% The Attempto Parsing Engine (APE) is free software: you can redistribute it and/or modify it
    5% under the terms of the GNU Lesser General Public License as published by the Free Software
    6% Foundation, either version 3 of the License, or (at your option) any later version.
    7%
    8% The Attempto Parsing Engine (APE) is distributed in the hope that it will be useful, but WITHOUT
    9% ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR
   10% PURPOSE. See the GNU Lesser General Public License for more details.
   11%
   12% You should have received a copy of the GNU Lesser General Public License along with the Attempto
   13% Parsing Engine (APE). If not, see http://www.gnu.org/licenses/.
   14
   15
   16:- module(error_logger,
   17	  [
   18	   clear_messages/0,
   19	   clear_messages/1,                     % +Type
   20	   clear_error_messages/0,
   21	   clear_error_messages_sentence/1,      % +Sentence
   22	   clear_warning_messages/0,
   23	   get_messages/1,                       % -Messages
   24	   get_messages_in_xml/1,                % -XmlMessages
   25	   get_error_messages/1,                 % -ErrorMessages
   26	   get_warning_messages/1,               % -WarningMessages
   27	   get_messages_with_type/2,             % +Type, -AllMessages
   28	   get_error_messages_with_type/2,       % +Type, -ErrorMessages
   29	   get_warning_messages_with_type/2,     % +Type, -WarningMessages
   30	   add_error_messagelist/4,              % +Type, +Position, +Subject, +DescriptionList
   31	   add_error_message/4,                  % +Type, +Position, +Subject, +Description
   32	   add_error_message_once/4,             % +Type, +Position, +Subject, +Description
   33	   add_warning_message/4,                % +Type, +Position, +Subject, +Description
   34	   add_warning_message_once/4,           % +Type, +Position, +Subject, +Description
   35	   add_messages/1,                       % +MessageList
   36	   is_error_message/4,                   % +Type, +Position, +Subject, +Description
   37	   messages_xmlmessages/2                % +Messages, -XmlMessages
   38	  ]).

APE Error Logger (using global variables)

author
- Tobias Kuhn
- Kaarel Kaljurand
version
- 2008-03-27 */
 clear_messages is det
bug
- Why do we need the cut + fallback in all the clearing predicates?
   53clear_messages :-
   54	setval(message, []).
 clear_messages(+Type:atom) is det
Clears all error and warnings messages of certain type.
Arguments:
Type- is in {syntax, anaphor, ...}
   63clear_messages(Type) :-
   64	getval(message, Messages),
   65	myexclude(message(_, Type, _, _, _), Messages, RemainingMessages),
   66	setval(message, RemainingMessages),
   67	!.
   68
   69clear_messages(_).
 clear_error_messages is det
Clears all error messages.
   76clear_error_messages :-
   77	getval(message, Messages),
   78	myexclude(message(error, _, _, _, _), Messages, RemainingMessages),
   79	setval(message, RemainingMessages),
   80	!.
   81
   82clear_error_messages.
 clear_warning_messages is det
Clears all warning messages.
   89clear_warning_messages :-
   90	getval(message, Messages),
   91	myexclude(message(warning, _, _, _, _), Messages, RemainingMessages),
   92	setval(message, RemainingMessages),
   93	!.
   94
   95clear_warning_messages.
 clear_error_messages_sentence is det
Arguments:
Sentence- is a sentence number

Clears all error messages of the given sentence.

  104clear_error_messages_sentence(Sentence) :-
  105	getval(message, Messages),
  106	myexclude(message(error, _, Sentence-_, _, _), Messages, RemainingMessages),
  107	setval(message, RemainingMessages),
  108	!.
  109
  110clear_error_messages_sentence(_).
 get_messages(-Messages:list) is det
Arguments:
Messages- is a list of terms message(Importance, Type, Position, Subject, Description)
  116get_messages(Messages) :-
  117	getval(message, MessagesR),
  118	reverse(MessagesR, Messages).
 get_messages_in_xml(-XmlMessages:term) is det
Arguments:
XmlMessages- is list of XML elements in SWI-Prolog notation
  125get_messages_in_xml(XmlMessages) :-
  126	get_messages(Messages),
  127	messages_xmlmessages(Messages, XmlMessages).
 messages_xmlmessages(+Messages:list, -XmlMessages:term) is det
Arguments:
Messages- is list of messages
XmlMessages- is list of XML elements in SWI-Prolog notation

A simple conversion of the message-terms into SWI-Prolog XML notation

  137messages_xmlmessages([], []).
  138
  139messages_xmlmessages(
  140	[message(Importance, Type, SentenceId-TokenId, Subject, Description) | Messages],
  141	[element(message, [importance=Importance, type=Type, sentence=SentenceId, token=TokenId, value=Subject, repair=Description], [])
  142		| XmlMessages]
  143	) :-
  144	messages_xmlmessages(Messages, XmlMessages).
 get_error_messages(-ErrorMessages:list) is det
Arguments:
ErrorMessages- is a list of terms message(Importance, Type, Position, Subject, Description)
  152get_error_messages(ErrorMessages) :-
  153	get_messages(Messages),
  154	findall(message(error, T, P, S, D), member(message(error, T, P, S, D), Messages), ErrorMessages).
 get_warning_messages(-WarningMessages:list) is det
Arguments:
WarningMessages- is a list of terms message(Importance, Type, Position, Subject, Description)
  161get_warning_messages(WarningMessages) :-
  162	get_messages(Messages),
  163	findall(message(warning, T, P, S, D), member(message(warning, T, P, S, D), Messages), WarningMessages).
 get_messages_with_type(+Type:atom, -AllMessages:list) is det
Arguments:
Type- is a message type, one of {sentence, word, owl, ...}
AllMessages- is a list of terms message(Importance, Type, Position, Subject, Description)
  171get_messages_with_type(Type, AllMessages) :-
  172	get_messages(Messages),
  173	findall(message(Importance, Type, P, S, D), member(message(Importance, Type, P, S, D), Messages), AllMessages).
 get_error_messages_with_type(+Type:atom, -ErrorMessages:list) is det
Arguments:
Type- is a message type, one of {sentence, word, owl, ...}
ErrorMessages- is a list of terms message(Importance, Type, Position, Subject, Description)
  181get_error_messages_with_type(Type, ErrorMessages) :-
  182	get_messages(Messages),
  183	findall(message(error, Type, P, S, D), member(message(error, Type, P, S, D), Messages), ErrorMessages).
 get_warning_messages_with_type(+Type:atom, -WarningMessages:list) is det
Arguments:
Type- is a message type, one of {sentence, word, owl, ...}
WarningMessages- is a list of terms message(Importance, Type, Position, Subject, Description)
  191get_warning_messages_with_type(Type, WarningMessages) :-
  192	get_messages(Messages),
  193	findall(message(warning, Type, P, S, D), member(message(warning, Type, P, S, D), Messages), WarningMessages).
 add_error_messagelist(+Type:atom, +Position:term, +Subject:atom, +DescriptionList:list) is det
Arguments:
Type- is in {syntax, anaphor, ...}
Position- is in the form SentenceId or SentenceId-TokenId
Subject- is usually the lexem in the position of the error
DescriptionList- is a list of messages that help to repair the error
  203add_error_messagelist(_Type, _Position, _Subject, []).
  204
  205add_error_messagelist(Type, Position, Subject, [H | T]) :-
  206	add_error_message(Type, Position, Subject, H),
  207	add_error_messagelist(Type, Position, Subject, T).
 add_error_message(+Type:atom, +Position:term, +Subject:atom, +Description:atom) is det
Arguments:
Type- is in {syntax, anaphor, ...}
Position- is in the form SentenceId or SentenceId-TokenId
Subject- is usually the lexem in the position of the error
Description- is a message that helps to repair the error
  217add_error_message(Type, Position, Subject, Description) :-
  218	assert_message(error, Type, Position, Subject, Description).
 add_error_message_once(+Type, +Position, +Subject, +Description) is det
  224add_error_message_once(Type, Position, Subject, Description) :-
  225	assert_message_once(error, Type, Position, Subject, Description).
 add_warning_message(+Type, +Position, +Subject, +Description) is det
  231add_warning_message(Type, Position, Subject, Description) :-
  232	assert_message(warning, Type, Position, Subject, Description).
 add_warning_message_once(+Type, +Position, +Subject, +Description) is det
  238add_warning_message_once(Type, Position, Subject, Description) :-
  239	assert_message_once(warning, Type, Position, Subject, Description).
 add_messages(+MessageList)
  245add_messages(MessageList) :-
  246	getval(message, OldMessages),
  247	reverse(MessageList, MessageListR),
  248	append(MessageListR, OldMessages, NewMessages),
  249	setval(message, NewMessages).
 assert_message(+Importance:atom, +Type:atom, +Position:term, +Subject:atom, +Description:atom) is det
Arguments:
Importance- is in {error, warning}
Type- is in {syntax, anaphor, ...}
Position- is in the form SentenceId or SentenceId-TokenId
Subject- is usually the lexem in the position of the error
Description- is a message that helps to repair the error
  260assert_message(Importance, Type, SentenceID-TokenID, Subject, Description) :-
  261    ground(message(Importance, Type, SentenceID-TokenID, Subject, Description)),
  262	!,
  263	% uncomment the next line for immediate print-out of the messages
  264	%write(message(Importance, Type, SentenceID-TokenID, Subject, Description)), nl,
  265	getval(message, Messages),
  266	setval(message, [message(Importance, Type, SentenceID-TokenID, Subject, Description) | Messages]).
  267
  268assert_message(Importance, Type, SentenceID-TokenID, Subject, Description) :-
  269    format(user_error, 'Malformed message: ~q\n', [message(Importance, Type, SentenceID-TokenID, Subject, Description)]),
  270    !.
  271
  272assert_message(Importance, Type, SentenceID, Subject, Description) :-
  273	assert_message(Importance, Type, SentenceID-'', Subject, Description).
 assert_message_once(+Importance, +Type, +Position, +Subject, +Description) is det
  279assert_message_once(Importance, Type, SentenceID-TokenID, Subject, Description) :-
  280	getval(message, Messages),
  281	member(message(Importance, Type, SentenceID-TokenID, Subject, Description), Messages),
  282	% message already exists
  283	!.
  284
  285assert_message_once(Importance, Type, SentenceID-TokenID, Subject, Description) :-
  286	!,
  287	assert_message(Importance, Type, SentenceID-TokenID, Subject, Description).
  288
  289assert_message_once(Importance, Type, SentenceID, Subject, Description) :-
  290	assert_message_once(Importance, Type, SentenceID-'', Subject, Description).
 is_error_message(+Type:atom, +Position:term, +Subject:atom, +Description:atom) is det
Succeeds if there is at least 1 error message (which the given characteristics)
  297is_error_message(Type, Position, Subject, Description) :-
  298	getval(message, Messages),
  299	member(message(error, Type, Position, Subject, Description), Messages),
  300	!.
 myexclude(+Element:term, +List1:list, -List2:list) is det
  306myexclude(_Element, [], []).
  307
  308myexclude(Element, [OtherElement | List1], [OtherElement | List2]) :-
  309	Element \= OtherElement,
  310	!,
  311	myexclude(Element, List1, List2).
  312
  313myexclude(Element, [_ | List1], List2) :-
  314	myexclude(Element, List1, List2).
 setval(+Name, +Value)
  320setval(Name, Value) :-
  321    nb_setval(Name, Value).
 getval(+Name, ?Value)
  327getval(Name, Value) :-
  328    nb_getval(Name, Value).
  329
  330
  331:- clear_messages.