34
35:- module(swish_profiles, []). 36:- use_module(library(lists)). 37:- use_module(library(readutil)). 38:- use_module(library(filesex)). 39:- use_module(library(dcg/basics)). 40
41:- multifile
42 user:file_search_path/2,
43 swish_config:config/2,
44 swish_config:source_alias/2. 45
47user:file_search_path(profile, swish(profiles)).
49swish_config:source_alias(profile, [access(read), search('*.{pl,swinb}')]).
50
51
60swish_config:config(profiles, Profiles) :-
61 findall(Profile, swish_profile(Profile), Profiles0),
62 sort(value, =<, Profiles0, Profiles1),
63 join_profiles(Profiles1, Profiles).
64
65join_profiles([], []).
66join_profiles([P1,P2|T0], [P|T]) :-
67 join_profiles(P1, P2, P), !,
68 join_profiles(T0, T).
69join_profiles([P|T0], [P1|T]) :-
70 P1 = P.put(type, [P.type]),
71 join_profiles(T0, T).
72
73join_profiles(P1, P2, profile{value:Name, type:[Ext1,Ext2],
74 label:Label, title:Title}) :-
75 P1 >:< _{value:Name, type:Ext1, label:Label1, title:Title1},
76 P2 >:< _{value:Name, type:Ext2, label:Label2, title:Title2},
77 join_value(Label1, Label2, Label),
78 join_value(Title1, Title2, Title).
79
80join_value(V, V, V) :- !.
81join_value(V, "No title", V) :- !.
82join_value("No title", V, V) :- !.
83join_value(V, _, V).
84
85swish_profile(profile{value:Name, type:Ext, label:Label, title:Title}) :-
86 absolute_file_name(profile(.), Dir,
87 [ file_type(directory),
88 access(read),
89 solutions(all)
90 ]),
91 directory_file_path(Dir, '*.{pl,swinb}', Pattern),
92 expand_file_name(Pattern, Files),
93 member(FilePath, Files),
94 file_base_name(FilePath, File),
95 file_name_extension(Name, Ext, File),
96 value_label(Name, Label),
97 title(FilePath, Title).
98
99value_label(Value, Label) :-
100 atom_codes(Value, Codes),
101 phrase(label(Label), Codes).
102
103label(Label) -->
104 string(_), "-", !, rest(Codes),
105 { string_codes(Label, Codes) }.
106label(Label) -->
107 rest(Codes),
108 { string_codes(Label, Codes) }.
109
110title(FilePath, Title) :-
111 first_line(FilePath, FirstLine),
112 ( FirstLine == end_of_file
113 -> Title = "Empty"
114 ; phrase(title(Title), FirstLine)
115 ).
116
117first_line(File, Line) :-
118 setup_call_cleanup(
119 open(File, read, In),
120 read_line_to_codes(In, Line),
121 close(In)).
122
123title(Title) -->
124 "%", whites, !, rest(Codes),
125 { string_codes(Title, Codes) }.
126title("No title") --> rest(_).
127
128rest(List, List, [])