1:- module(onepointfour_basics_checks_print_error_message,
    2          [
    3          % there is actually nothing to export
    4          ]).    5
    6/*  MIT License Follows (https://opensource.org/licenses/MIT)
    7
    8    Copyright 2021 David Tonhofer <ronerycoder@gluino.name>
    9
   10    Permission is hereby granted, free of charge, to any person obtaining
   11    a copy of this software and associated documentation files
   12    (the "Software"), to deal in the Software without restriction,
   13    including without limitation the rights to use, copy, modify, merge,
   14    publish, distribute, sublicense, and/or sell copies of the Software,
   15    and to permit persons to whom the Software is furnished to do so,
   16    subject to the following conditions:
   17
   18    The above copyright notice and this permission notice shall be
   19    included in all copies or substantial portions of the Software.
   20
   21    THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
   22    EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
   23    MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.
   24    IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY
   25    CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT,
   26    TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE
   27    SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
   28*/
   29
   30
   31/* pldoc ==================================================================== */

Hooking into the toplevel error printer

Code in the module hooks into the toplevel error printer (error_message//1) in order to properly printing the non-ISO error term

error(check(_,_,_,_),_)

thrown from "check" predicates.

The homepage for this module is at

https://github.com/dtonhofer/prolog_code/blob/main/unpacked/onepointfour_basics/README_checks.md

*/

   48:- multifile prolog:error_message//1.  % 1-st argument of error term
   49
   50% Type     : An atom, describing the "type" of the error. We know of the following:
   51%
   52%            domain          : the culprit is outside the required domain
   53%            type            : the culprit is not of the required type
   54%            uninstantiation : the culprit is already (fully) instantiated
   55%            instantiation   : the culprit is not instantiated (enough)
   56%            random          : this is a random error due to the outcome of maybe/1
   57%            call            : there is no check_that/N matching the call
   58%
   59% Expected : A cleartext description or a term describing what was actually expected 
   60%            but not encountered. Will be printed on a single line after the
   61%            text "expected: ". If this is a var, the line is suppressed.
   62%
   63% Msg      : A cleartext message about what's going on. Will be printed on a 
   64%            single line after the text "messag: ". If this is a var, the
   65%            line is suppressed.
   66%
   67% Culprit  : The term this is the reason of the error, for example it might be
   68%            the atom encountered when an integer was expected.
   69%            A special case is the Culprit being an uninstantiated variable.
   70
   71prolog:error_message(check(Type,Expected,Msg,Culprit)) -->
   72    { build_main_text_pair(Type,MainTextPair) },
   73    [ MainTextPair, nl ],
   74    lineify_expected(Expected),
   75    lineify_msg(Msg),
   76    lineify_culprit(Type,Culprit).
   77 
   78% Build a pair TextWithPlaceholders-ListOfParameters for the toplevel printer
   79
   80build_main_text_pair(Type,MainTextPair) :-
   81   extended_msg(Type,ExMsg), 
   82   !,
   83   transform_to_string(ExMsg,ExMsgStr),
   84   transform_to_string(Type,TypeStr),
   85   MainTextPair = 'check failed : \'~s\' error (~s)'-[TypeStr,ExMsgStr].
   86
   87build_main_text_pair(Type,MainTextPair) :-
   88   transform_to_string(Type,TypeStr),
   89   MainTextPair = 'check failed : \'~s\' error'-[TypeStr].
   90
   91% Define messages for specific error types.
   92% If none has been defined, a generic one is created in build_main_text_pair/2.
   93
   94extended_msg(domain,          "the culprit is outside the required domain").
   95extended_msg(type,            "the culprit is not of the required type").
   96extended_msg(uninstantiation, "the culprit is already (fully) instantiated").
   97extended_msg(instantiation,   "the culprit is not instantiated (enough)").
   98extended_msg(random,          "this is a random error due to the outcome of maybe/1").
   99extended_msg(call,            "there is no check_that/N matching the actual call").
  100
  101% Transforming o SWI-Prolog string, avoiding quotes
  102
  103transform_to_string(X,X) :-
  104   string(X),
  105   !.
  106transform_to_string(X,Str) :-
  107   atom(X),
  108   !,
  109   atom_string(X,Str).
  110transform_to_string(X,Str) :-
  111   format(string(Str),"~q",[X]).
  112
  113% generate the "expected:" line information
  114
  115lineify_expected(Expected) -->
  116   { nonvar(Expected), transform_to_string(Expected,ExpectedStr) },
  117   !,
  118   [ '   expected  : ~s'-[ExpectedStr], nl ].
  119lineify_expected(_) --> [].
  120
  121% generate the "message:" line information
  122
  123lineify_msg(Msg) -->
  124   { nonvar(Msg), transform_to_string(Msg,MsgStr) },
  125   !,
  126   [ '   message   : ~s'-[MsgStr], nl ].
  127lineify_msg(_) --> [].
  128
  129% generate the "culprit:" line information
  130
  131lineify_culprit(Type,Culprit) -->
  132   { nonvar(Culprit), Type\==random, transform_to_string(Culprit,CulpritStr) },
  133   !,
  134   [ '   culprit   : ~s'-[CulpritStr], nl ].
  135lineify_culprit(_,_) --> []