1:- module(onepointfour_basics_dict_settings,
    2          [
    3           get_setting/3  % get_setting(+SettingsDict,+Key,?Value)
    4          ,get_setting/4  % get_setting(+SettingsDict,+Key,?Value,+Default)
    5          ,get_setting_tuned/4 % get_setting_tuned(SettingsDict,Key,Value,Tuned)
    6          ]).    7
    8/*  Zero-Clause BSD (0BSD) follows (https://opensource.org/licenses/0BSD)
    9
   10    Permission to use, copy, modify, and/or distribute this software for
   11    any purpose with or without fee is hereby granted.
   12
   13    THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL
   14    WARRANTIES WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED
   15    WARRANTIES OF MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE
   16    AUTHOR BE LIABLE FOR ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL
   17    DAMAGES OR ANY DAMAGES WHATSOEVER RESULTING FROM LOSS OF USE, DATA
   18    OR PROFITS, WHETHER IN AN ACTION OF CONTRACT, NEGLIGENCE OR OTHER
   19    TORTIOUS ACTION, ARISING OUT OF OR IN CONNECTION WITH THE USE OR
   20    PERFORMANCE OF THIS SOFTWARE.
   21*/
   22
   23/*
   24 * Simple predicates to extract a value from a dict or provide a default instead.
   25 */
 get_setting(+SettingsDict, +Key, ?Value, +Default)
Instantiate Value to the value stored under Key in SettingsDict. If it is missing, unifies Value with Default.
   32get_setting(SettingsDict,Key,Value,_Default) :-
   33   get_dict(Key,SettingsDict,Value2),             % get_dict/3 succeeds if entry with "Key" exists
   34   !,
   35   Value=Value2.
   36get_setting(_,_,ValueIsDefault,ValueIsDefault).   % fallback to "Default"
 get_setting_tuned(+SettingsDict, +Key, ?Value, @Tuned)
Same as get_setting/3, but with Tuned = 'soft', the predicate just fail instead of throwing. Set Tuned = 'hard' (or anything else) to recover get_setting/3 behaviour
   44get_setting_tuned(SettingsDict,Key,Value,Tuned) :-
   45   (Tuned==soft)
   46   ->
   47   get_setting(SettingsDict,Key,Value2,Default),
   48   (
   49      (Value2\==Default)
   50      ->
   51      Value=Value2   % entry was found, unify
   52      ;
   53      fail           % entry does not exist, fail
   54   )
   55   ;
   56   get_setting(SettingsDict,Key,Value).
 get_setting(+SettingsDict, +Key, ?Value)
Instantiate Value to the value stored under Key in SettingsDict. If it is missing a (non-ISO) error term error(dict_error(missing_entry,Key)) is thrown.
   64get_setting(SettingsDict,Key,Value) :-
   65   get_dict(Key,SettingsDict,Value2),             % get_dict/3 succeeds if entry with "Key" exists
   66   !,
   67   Value=Value2.
   68get_setting(_SettingsDict,Key,_) :-
   69   throw(error(dict_error(missing_entry,Key),_)).
   70
   71% Properly printing the error(dict_error(missing_entry,_,_,_),_) exception term
   72% by adding rules to the prolog::error_message//1 multifile DCG rule.
   73
   74:- multifile prolog:error_message//1.  % 1-st argument of error term
   75
   76prolog:error_message(dict_error(missing_entry,Key)) -->
   77   [ "expected dict entry, which was missing", nl, "dict key: ~q"-Key, nl ]