1:- module(bc_api_io, [
    2    bc_reply_success/1, % +Dict
    3    bc_reply_error/1,   % +Message
    4    bc_read_by_schema/2 % +Schema, -Dict
    5]).    6
    7:- use_module(library(http/http_json)).    8:- use_module(library(http/http_wrapper)).    9:- use_module(library(dict_schema)).
 bc_read_by_schema(+Schema, -Dict) is det
Reads dict from JSON request and validates it against the schema. Throws error(invalid_input(Errors)) when input data contains validation errors.
   18bc_read_by_schema(Schema, Dict):-
   19    http_current_request(Request),
   20    http_read_json_dict(Request, Raw),
   21    convert(Raw, Schema, Dict, Errors),
   22    (   Errors = []
   23    ;   throw(error(invalid_input(Errors)))), !.
 bc_reply_success(+Data) is det
Sends JSON response with Data and success status.
   30bc_reply_success(Data):-
   31    write('Cache-Control: no-cache\r\n'),
   32    reply_json(_{ status: success, data: Data }).
 bc_reply_error(+Message) is det
Sends error JSON response with Message.
   38bc_reply_error(Message):-
   39    write('Cache-Control: no-cache\r\n'),
   40    reply_json(_{ status: error, message: Message })