
% set of rules to handle queries about file archive data
%
% an archive is a list of lists, where each sublist is the
%    information regarding one archived file, and consists
%    of the following elements (in order)
%    [ base_filename, archive_directory, owner, modification_time, filesize ]
%    (where modification time is seconds since the epoch and file size is bytes)
% e.g. an archive for just one file might look like
%    [["foo.txt", "/archives/data/2019", "jdoe", 1552240465, 1903]]
% and an archive containing two files might look like
%    [["file1", "/home/whoever/archive", "whoever", 1230005, 10017],
%     ["anotherFile", "/misc/archive", "someone", 973024601, 200]]

% Queries supported
% -----------------
% validFileInfo(F)
%    succeeds iff F has the valid format for a file record,
%    i.e. [ string, string, string, posInt, posInt ]
% dateRange(Archive, FileList, StartTime, EndTime)
%    gets the list of records for all files whose modification time is within
%    the given range
% oldest(Archive, FileList, ModTime)
%    gets the list of records for all files with the oldest modification time
%    (i.e. lowest number) - it is a list in case multiple files have an equal
%    oldest date
% largest(Archive, FileList)
%    gets the list of records for all files with the largest size (in bytes)
%    Again, it is a list in case multiple files have an equal largest size
% ownerFiles(Archive, Owner, FileList)
%    gets the list of records for all files belonging to the specified owner
% dirFiles(Archive, Dir, FileList)
%    gets the list of records for all files in the specified directory
% fileVersions(Archive, FileBaseName, FileList)
%    gets the list of records for all files matching the specified base name


% okInt(I, Min)
% -------------
% succeeds iff I and Min are integers, I >= Min
okInt(I, Min) :- integer(I), integer(Min), I >= Min.


% validFileInfo(F)
% ----------------
%    succeeds iff F has the valid format for a file record,
%    i.e. [ string, string, string, posInt, posInt ]
validFileInfo([Fname, Dir, Owner, Time, Size]) :-
   string(Fname), string(Dir), string(Owner), okInt(Time, 0), okInt(Size, 0).


% dateRange(Archive, FileList, StartTime, EndTime)
% ------------------------------------------------
%    gets the list of records for all files whose modification time is within
%    the given range
dateRange([], [], _, _).
dateRange([H|T], [H|Rest], Start, End) :- okInt(Start, 0), okInt(End, Start),
   validFileInfo(H), H = [ _, _, _, Time, _ ], okInt(Time, Start),
   End >= Time, dateRange(T, Rest, Start, End).
dateRange([_|T], Rest, Start, End) :- okInt(Start, 0), okInt(End, Start),
   dateRange(T, Rest, Start, End).


% oldest(Archive, FileList, ModTime)
% ----------------------------------
%    gets the list of records for all files with the oldest modification time
%    (i.e. lowest number) - it is a list in case multiple files have an equal
%    oldest date

% base cases, zero or one item
oldest([], [], Time) :- get_time(Time).  % assumes latest possible time is NOW
oldest([H], [H], Time) :- validFileInfo(H), H = [_, _, _, Time, _].

% H isn't valid, skip it and process the rest
oldest([H|Rest], L, Time) :- not(validFileInfo(H)), oldest(Rest,L, Time).

% H is older than anything in the rest
oldest([H|Rest], [H], Time) :- validFileInfo(H), H = [_, _, _, Time, _],
   oldest(Rest, _, RTime), Time < RTime.

% H is same age as oldest stuff in the rest
oldest([H|Rest], [H|Old], Time) :- validFileInfo(H), H = [_, _, _, Time, _],
   oldest(Rest, Old, Time).

% H is not as old as oldest stuff in the rest
oldest([H|Rest], Old, Time) :- validFileInfo(H), H = [_, _, _, HTime, _],
   oldest(Rest, Old, Time), HTime > Time.

% largest(Archive, FileList)
% --------------------------
%    gets the list of records for all files with the largest size (in bytes)
%    Again, it is a list in case multiple files have an equal largest size

% base case, no items or only one item
largest([], [], Size) :- Max is 2^32, Max = Size. % assumes largest file size is 4GB
largest([H], [H], Size) :- validFileInfo(H), H = [_, _, _, _, Size].

% H isn't valid, skip it and process the rest
largest([H|Rest], L, Size) :- not(validFileInfo(H)), largest(Rest,L, Size).

% H is larger than anything in the rest
largest([H|Rest], [H], Size) :- validFileInfo(H), H = [_, _, _, _, Size],
   largest(Rest, _, RSize), Size > RSize.

% H is same size as largest stuff in the rest
largest([H|Rest], [H|Old], Size) :- validFileInfo(H), H = [_, _, _, _, Size],
   largest(Rest, Old, Size).

% H is not as large as largest stuff in the rest
largest([H|Rest], Old, Size) :- validFileInfo(H), H = [_, _, _, _, HSize],
   largest(Rest, Old, Size), HSize < Size.


% ownerFiles(Archive, Owner, FileList)
% ------------------------------------
%    gets the list of records for all files belonging to the specified owner
ownerFiles([], _, []).
ownerFiles([H], Owner, [H]) :- validFileInfo(H), H = [_, _, Owner, _, _].
ownerFiles([H|T], Owner, [H|Rest]) :- validFileInfo(H),
   H = [_, _, Owner, _, _], ownerFiles(T, Owner, Rest).
ownerFiles([_|T], Owner, Rest) :- ownerFiles(T, Owner, Rest).


% dirFiles(Archive, Dir, FileList)
% --------------------------------
%    gets the list of records for all files in the specified directory
dirFiles([], _, []).
dirFiles([H], Dir, [H]) :- validFileInfo(H), H = [_, Dir, _, _, _].
dirFiles([H|T], Dir, [H|Rest]) :- validFileInfo(H),
   H = [_, Dir, _, _, _], dirFiles(T, Dir, Rest).
dirFiles([_|T], Dir, Rest) :- dirFiles(T, Dir, Rest).


% fileVersions(Archive, FileBaseName, FileList)
% ---------------------------------------------
%    gets the list of records for all files matching the specified base name
fileVersions([], _, []).
fileVersions([H], Fname, [H]) :- validFileInfo(H), H = [Fname, _, _, _, _].
fileVersions([H|T], Fname, [H|Rest]) :- validFileInfo(H),
   H = [Fname, _, _, _, _], fileVersions(T, Fname, Rest).
fileVersions([_|T], Fname, Rest) :- fileVersions(T, Fname, Rest).


% ---------------- Sample Test Data -------------------
% loadTest(Num, Data)
% -------------------
% loads the test case data with the specified number

% test case 0 is empty archive
testcase(0, []).

% test case 1: single entry
testcase(1, [ ["file1", "/home/whoever/archive", "whoever", 123, 200] ]).  

% test case 2: two entries in same archive with same owner
testcase(2, [
    ["file1", "/home/whoever/archive", "whoever", 123, 100],
    ["file2", "/home/whoever/archive", "whoever", 246, 200]
   ]).  

% test case 3: three entries in different archives with different owners
testcase(3, [
    ["file1", "/home/whoever/archive", "whoever", 123, 100],
    ["file2", "/home/someone/archive", "someone", 246, 200],
    ["file3", "/home/another/archive", "another", 100, 150]
   ]).  

% test case 4: four distinct entries with overlapping field values
%  - two with the same matching oldest date
%  - two with the same largest size
%  - two with the same filename
%  - two in the same directory
%  - two with the same owner
testcase(4, [
    ["file4", "/home/whoever/archive", "whoever", 100, 200],
    ["file1", "/home/someone/archive", "someone", 246, 200],
    ["file2", "/home/someone/archive", "another", 100, 100],
    ["file1", "/home/extra/archive", "whoever", 123, 150]
   ]).  

