Skip to content

Instantly share code, notes, and snippets.

@rindPHI
Last active June 15, 2021 08:01
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save rindPHI/d1e943017491b046ebc76e9ee44d11e2 to your computer and use it in GitHub Desktop.
Save rindPHI/d1e943017491b046ebc76e9ee44d11e2 to your computer and use it in GitHub Desktop.
Prolog program for preference-based assignments (e.g., papers to students)
:- use_module(library(clpfd)).
:- use_module(library(aggregate)).
% How to use:
%
% - Add preference(student, paper_id, pref_value) facts for the preferences of all students
% (see end of file!)
% - student is any kind of value, e.g., strings or atoms
% - paper_id is a numeric identifier starting a 0
% - pref_value is a numeric value. Higher values indicate higher preferences
% - If there are N students, there should be N preference facts for each student
% - Furthermore, there have to be at least N papers
% - For each paper id, optionally add a paper_title(paper_id, title) fact for showing titles,
% and not ids, in the output
% - Then, call ":- solution(S)" to produce one optimal assignment. If there are multiple
% optimal assignments, a random optimal assignment is returned.
%%% Assignments and Scores
assignment(A) :-
students(Students),
length(Students, L),
length(Papers, L),
term_variables(Papers, Vars),
all_distinct(Vars),
papers(AllPapers),
max_list(AllPapers, M),
Vars ins 0..M,
permutation(Papers, PapersPerm),
permutation(Students, StudentsPerm),
zip(StudentsPerm, PapersPerm, A).
score([], 0).
score([A|Tl], R) :-
A = St-Pa,
preference(St, Pa, Pr),
score(Tl, Sub),
R #= Pr + Sub.
%%% Computing a Solution
solution(R) :-
aggregate_all(
max(S, O),
(
assignment(A),
score(A, S),
maplist([Assgn, Out]>>(
Assgn = Student-PaperId,
(
paper_title(PaperId, PaperTitle),
Out = Student-PaperTitle
) ; Out = Assgn
), A, O)
),
R).
%%% Utility Predicates
paper(P) :- preference(_, P, _).
papers(R) :- aggregate_all(set(P), paper(P), R).
student(S) :- preference(S, _, _).
students(R) :- aggregate_all(set(S), student(S), R).
zip(L1, L2, R) :- maplist([A, B, Out]>>(Out = A-B), L1, L2, R).
% Ensures that there is no error if no paper titles are defined
:- discontiguous paper_title/2.
paper_title(-1, "").
%%% DATA %%%
% preference/3: Triples (student, paper_id, preference value)
preference("Dominic", 0, 10).
preference("Dominic", 1, 9).
preference("Dominic", 2, 8).
preference("Alice", 0, 10).
preference("Alice", 1, 8).
preference("Alice", 2, 9).
% paper_title/2: *Optional* definitions of paper titles for IDs
paper_title(0, "QuickSpec").
paper_title(1, "Alhazen").
paper_title(1, "Beginner's Luck").
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment