1:- module(bc_access, [
2 bc_read_access_id/2, 3 bc_read_access_entry/2, 4 bc_remove_access_id/2, 5 bc_remove_access_entry/2, 6 bc_update_access_id/2, 7 bc_create_access_type/2, 8 bc_files_access_id/2, 9 bc_publish_access_id/2, 10 bc_login_access/1 11]). 12
13:- use_module(library(error)). 14:- use_module(bc_type). 15:- use_module(bc_role). 16:- use_module(bc_entry). 17
20
21bc_read_access_entry(Actor, _):-
22 Actor.type = admin, !.
23
24bc_read_access_entry(Actor, Entry):-
25 bc_type_actor_grants(Entry.type, Actor, Grants),
26 ( member(read_any, Grants)
27 ; member(read_own, Grants),
28 Actor.'$id' = Entry.author), !.
29
32
33bc_read_access_id(Actor, _):-
34 Actor.type = admin, !.
35
36bc_read_access_id(Actor, Id):-
37 bc_entry_type(Id, Type),
38 bc_type_actor_grants(Type, Actor, Grants),
39 ( member(read_any, Grants)
40 ; member(read_own, Grants),
41 bc_entry_author(Id, AuthorId),
42 Actor.'$id' = AuthorId), !.
43
46
47bc_remove_access_id(Actor, _):-
48 Actor.type = admin, !.
49
50bc_remove_access_id(Actor, Id):-
51 bc_entry_type(Id, Type),
52 bc_type_actor_grants(Type, Actor, Grants),
53 ( member(remove_any, Grants)
54 ; member(remove_own, Grants),
55 bc_entry_author(Id, AuthorId),
56 Actor.'$id' = AuthorId), !.
57
60
61bc_remove_access_entry(Actor, _):-
62 Actor.type = admin, !.
63
64bc_remove_access_entry(Actor, Entry):-
65 bc_type_actor_grants(Entry.type, Actor, Grants),
66 ( member(remove_any, Grants)
67 ; member(remove_own, Grants),
68 Actor.'$id' = Entry.author), !.
69
72
73bc_update_access_id(Actor, _):-
74 Actor.type = admin, !.
75
76bc_update_access_id(Actor, Id):-
77 bc_entry_type(Id, Type),
78 bc_type_actor_grants(Type, Actor, Grants),
79 ( member(update_any, Grants)
80 ; member(update_own, Grants),
81 bc_entry_author(Id, AuthorId),
82 Actor.'$id' = AuthorId), !.
83
86
87bc_create_access_type(Actor, _):-
88 Actor.type = admin, !.
89
90bc_create_access_type(Actor, Type):-
91 bc_type_actor_grants(Type, Actor, Grants),
92 memberchk(create, Grants).
93
96
97bc_files_access_id(Actor, _):-
98 Actor.type = admin, !.
99
100bc_files_access_id(Actor, Id):-
101 bc_entry_type(Id, Type),
102 bc_type_actor_grants(Type, Actor, Grants),
103 memberchk(files, Grants).
104
107
108bc_publish_access_id(Actor, _):-
109 Actor.type = admin, !.
110
111bc_publish_access_id(Actor, Id):-
112 bc_entry_type(Id, Type),
113 bc_type_actor_grants(Type, Actor, Grants),
114 bc_entry_author(Id, AuthorId),
115 ( member(publish_any, Grants)
116 ; member(publish_own, Grants),
117 Actor.'$id' = AuthorId), !.
118
121
122bc_login_access(Actor):-
123 bc_role(Actor.type, _, true).
124
129
130bc_type_actor_grants(Type, Actor, Grants):-
131 bc_type(Type, _, _, Roles, _),
132 member(Role, Roles),
133 Role =.. [Name|Grants],
134 Actor.type = Name, !