1:- module(bc_api_type, []).

Type API handlers */

    5:- use_module(library(arouter)).    6
    7:- use_module(bc_api_io).    8:- use_module(bc_api_auth).    9:- use_module(bc_api_actor).   10:- use_module(bc_type).   11
   12:- route_get(api/types,
   13    bc_auth, types).   14
   15:- route_get(api/type/Type,
   16    bc_auth, type(Type)).   17
   18types:-
   19    bc_actor(User),
   20    accessible_types(User, Types),
   21    bc_reply_success(Types).
   22
   23type(Type):-
   24    bc_actor(User),
   25    accessible_type(User, Type, Data),
   26    bc_reply_success(Data).
   27
   28% Entry types that user has access to.
   29
   30accessible_types(User, Types):-
   31    findall(
   32        _{  name: Name,
   33            label: Label,
   34            menu_label: MenuLabel,
   35            grants: Grants,
   36            comments: Comments,
   37            preview: Preview },
   38        (
   39            bc_type(Name, Label, MenuLabel, Roles, Comments),
   40            member(Role, Roles),
   41            Role =.. [RoleName|Grants],
   42            User.type = RoleName,
   43            type_preview(Name, Preview)
   44        ), Types).
   45
   46accessible_type(User, Name, Data):-
   47    Data = _{
   48        name: Name,
   49        label: Label,
   50        menu_label: MenuLabel,
   51        grants: Grants,
   52        comments: Comments,
   53        preview: Preview },
   54    bc_type(Name, Label, MenuLabel, Roles, Comments),
   55    member(Role, Roles),
   56    Role =.. [RoleName|Grants],
   57    User.type = RoleName,
   58    type_preview(Name, Preview).
   59
   60accessible_type(_, _, _):-
   61    throw(error(no_access)).
   62
   63% Gives the type preview or null
   64% when the preview does not exist.
   65
   66type_preview(Name, Preview):-
   67    bc_type_preview(Name, Preview), !.
   68
   69type_preview(_, null)