Daniel@0
|
1 /* Part of DML (Digital Music Laboratory)
|
Daniel@0
|
2 Copyright 2014-2015 Samer Abdallah, University of London
|
Daniel@0
|
3
|
Daniel@0
|
4 This program is free software; you can redistribute it and/or
|
Daniel@0
|
5 modify it under the terms of the GNU General Public License
|
Daniel@0
|
6 as published by the Free Software Foundation; either version 2
|
Daniel@0
|
7 of the License, or (at your option) any later version.
|
Daniel@0
|
8
|
Daniel@0
|
9 This program is distributed in the hope that it will be useful,
|
Daniel@0
|
10 but WITHOUT ANY WARRANTY; without even the implied warranty of
|
Daniel@0
|
11 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
Daniel@0
|
12 GNU General Public License for more details.
|
Daniel@0
|
13
|
Daniel@0
|
14 You should have received a copy of the GNU General Public
|
Daniel@0
|
15 License along with this library; if not, write to the Free Software
|
Daniel@0
|
16 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
|
Daniel@0
|
17 */
|
Daniel@0
|
18
|
Daniel@0
|
19 :- module(dml,
|
Daniel@0
|
20 [ call_debugging/2
|
Daniel@0
|
21 , call_nodebug/1
|
Daniel@0
|
22 , view_computations/0
|
Daniel@0
|
23 , start_matlab/0
|
Daniel@0
|
24 , stop_matlab/0
|
Daniel@0
|
25 , start_r_server/0
|
Daniel@0
|
26 , update/1 ]).
|
Daniel@0
|
27
|
Daniel@0
|
28 /** <module> DML main loader
|
Daniel@0
|
29 */
|
Daniel@0
|
30
|
Daniel@0
|
31 :- set_prolog_flag(double_quotes, string).
|
Daniel@0
|
32 :- debug_message_context(+time('%FT%T')).
|
Daniel@0
|
33
|
Daniel@0
|
34 user:file_search_path(memo, cp_application(memo_db)).
|
Daniel@0
|
35
|
Daniel@0
|
36 :- use_module(cp_application('config-enabled/dml_permission')).
|
Daniel@0
|
37
|
Daniel@0
|
38 :- use_module(library(rcutils)).
|
Daniel@0
|
39 :- use_module(library(http/http_dispatch)).
|
Daniel@0
|
40 :- use_module(skin(minimal)).
|
Daniel@0
|
41 :- use_module(library(dml_data)).
|
Daniel@0
|
42 :- use_module(applications(callgraph_ui)).
|
Daniel@0
|
43 :- use_module(applications(audio_ui)).
|
Daniel@0
|
44 :- use_module(applications(score_ui)).
|
Daniel@0
|
45 :- use_module(applications(csv_ui)).
|
Daniel@0
|
46 :- use_module(applications(memo_ui)).
|
Daniel@0
|
47 :- use_module(applications(transcription_ui)).
|
Daniel@0
|
48 :- use_module(applications(dml_overview)).
|
Daniel@0
|
49
|
Daniel@0
|
50 :- use_module(library(code_cache)).
|
Daniel@0
|
51 :- use_module(library(dml_crawler)).
|
Daniel@0
|
52 :- use_module(library(dml_spotify)).
|
Daniel@0
|
53 :- use_module(library(dml_musicbrainz)).
|
Daniel@0
|
54 :- use_module(library(dml_swish)).
|
Daniel@0
|
55 :- use_module(library(dml_misc)).
|
Daniel@0
|
56 :- use_module(library(musiclab)).
|
Daniel@0
|
57 :- use_module(library(rdfutils)).
|
Daniel@0
|
58 :- use_module(library(dlogic)).
|
Daniel@0
|
59 :- use_module(library(dataset)).
|
Daniel@0
|
60 :- use_module(library(mlserver), except([start_matlab/0,start_matlab/1])).
|
Daniel@0
|
61 :- use_module(library(real)).
|
Daniel@0
|
62 :- use_module(library(backend_json)).
|
Daniel@0
|
63 :- use_module(library(dovamp)).
|
Daniel@0
|
64 :- use_module(api(matlab)).
|
Daniel@0
|
65 :- use_module(api(r_plot)).
|
Daniel@0
|
66 :- use_module(api(archive)).
|
Daniel@0
|
67 :- use_module(api(dmlvis)).
|
Daniel@0
|
68 :- use_module(api(perspectives)).
|
Daniel@0
|
69 :- use_module(api(transcription)).
|
Daniel@0
|
70 :- use_module(components(audio)).
|
Daniel@0
|
71 :- use_module(cliopatria(hooks)).
|
Daniel@0
|
72
|
Daniel@0
|
73 cliopatria_openid:insecure_host('mirg.city.ac.uk').
|
Daniel@0
|
74
|
Daniel@0
|
75
|
Daniel@0
|
76 % Hooks for audio related services
|
Daniel@0
|
77 cp_audio:audio_file(URI,File,Fmt) :- beets_p2r:audio_file(URI,File,Fmt).
|
Daniel@0
|
78 cp_audio:audio_file(URI,File,Fmt) :- charm_p2r:audio_file(URI,File,Fmt).
|
Daniel@0
|
79 cp_audio:audio_file(URI,File,Fmt) :- bl_p2r:audio_file(URI,File,Fmt).
|
Daniel@0
|
80 cp_audio:audio_file(URI,File,Fmt) :- mazurka_p2r:audio_file(URI,File,Fmt).
|
Daniel@0
|
81
|
Daniel@0
|
82 cp_audio:audio_link(URI,Link,just(mp3)) :- bl_p2r:audio_link(URI,Link).
|
Daniel@0
|
83 cp_audio:audio_link(URI,URL,just(Fmt)) :-
|
Daniel@0
|
84 bl_p2r:audio_file(URI,File,just(Fmt)),
|
Daniel@0
|
85 file_permission(File,public),
|
Daniel@0
|
86 http_link_to_id(audio_get,[uri(URI),format(Fmt)],URL).
|
Daniel@0
|
87 cp_audio:audio_link(URI,Link,just(mp3)) :- charm_p2r:audio_link(mp3,URI,Link).
|
Daniel@0
|
88 cp_audio:audio_link(URI,URL,just(Fmt)) :-
|
Daniel@0
|
89 Formats=[ogg,mp3], % in order of preference
|
Daniel@0
|
90 ( beets_p2r:audio_file(URI,File,just(Orig))
|
Daniel@0
|
91 ; mazurka_p2r:audio_file(URI,File,just(Orig))
|
Daniel@0
|
92 ),
|
Daniel@0
|
93 file_permission(File,public),
|
Daniel@0
|
94 (member(Orig,Formats) -> member(Fmt,Formats); member(Fmt,[Orig|Formats])),
|
Daniel@0
|
95 http_link_to_id(audio_get,[uri(URI),format(Fmt)],URL).
|
Daniel@0
|
96
|
Daniel@0
|
97 %:- rdf_set_cache_options([enabled(true),global_directory(cache)]).
|
Daniel@0
|
98
|
Daniel@0
|
99 % ------------------ string portrayal -------------
|
Daniel@0
|
100 % user:portray(String) :-
|
Daniel@0
|
101 % string(String), !,
|
Daniel@0
|
102 % truncate(50,String,Short),
|
Daniel@0
|
103 % writeq(Short).
|
Daniel@0
|
104
|
Daniel@0
|
105 % truncate(Max,S,S) :- string_length(S,L), L<Max, !.
|
Daniel@0
|
106 % truncate(Max,S1,S3) :-
|
Daniel@0
|
107 % L is Max-3,
|
Daniel@0
|
108 % sub_string(S1,0,L,_,S2),
|
Daniel@0
|
109 % string_concat(S2,"...",S3).
|
Daniel@0
|
110
|
Daniel@0
|
111 % Adjust menus
|
Daniel@0
|
112 cliopatria:menu_item(900=query/isearch, 'Interactive faceted search').
|
Daniel@0
|
113 cliopatria:menu_item(900=places/http_skos_browser, 'SKOS Concept browser').
|
Daniel@0
|
114 cliopatria:menu_item(800=help/dml_overview, 'DML overview').
|
Daniel@0
|
115 cliopatria:menu_item(800=admin/job_view, 'Current jobs').
|
Daniel@0
|
116
|
Daniel@0
|
117 warm_indices :-
|
Daniel@0
|
118 ignore(rdf(s, _, _)),
|
Daniel@0
|
119 ignore(rdf(_, p, _)),
|
Daniel@0
|
120 ignore(rdf(_, _, o)),
|
Daniel@0
|
121 ignore(rdf(s, p, _)),
|
Daniel@0
|
122 ignore(rdf(_, p, o)),
|
Daniel@0
|
123 ignore(rdf(s, p, o)),
|
Daniel@0
|
124 ignore(rdf(_, _, _, g)),
|
Daniel@0
|
125 ignore(rdf(s, _, _, g)),
|
Daniel@0
|
126 ignore(rdf(_, p, _, g)).
|
Daniel@0
|
127
|
Daniel@0
|
128 % :- rdf_register_prefix(dmlcla,'http://dml.org/cla#').
|
Daniel@0
|
129 % :- initialization rdf_load(dml('cla/ontologies/dmlclaOntology.n3')).
|
Daniel@0
|
130 :- initialization open_log, maplist(debug,[dmlvis(perspective),dmlvis(error),dmlvis(response)]).
|
Daniel@0
|
131 :- initialization persistent_history('.dml.history',[interval(300)]), confirm_on_halt.
|
Daniel@0
|
132 :- initialization p2r_import(memo_p2r).
|
Daniel@0
|
133 :- initialization
|
Daniel@0
|
134 ( current_periodical(_,clean_code_cache(_),Id)
|
Daniel@0
|
135 -> remove_periodical(Id)
|
Daniel@0
|
136 ; true
|
Daniel@0
|
137 ),
|
Daniel@0
|
138 periodically(3600,clean_code_cache(3600)).
|
Daniel@0
|
139
|
Daniel@0
|
140 :- dynamic log_stream/1.
|
Daniel@0
|
141 open_log :-
|
Daniel@0
|
142 (log_stream(S) -> close(S), retractall(log_stream(_)); true),
|
Daniel@0
|
143 expand_file_name('~/var/log/dml.log',[LogFile]),
|
Daniel@0
|
144 open(LogFile,append,LogStream,[buffer(line)]), nl(LogStream),
|
Daniel@0
|
145 assert(log_stream(LogStream)),
|
Daniel@0
|
146 debug(log), debug(log,'Started logging.',[]).
|
Daniel@0
|
147
|
Daniel@0
|
148
|
Daniel@0
|
149 :- meta_predicate call_debugging(?,0), call_nodebug(0).
|
Daniel@0
|
150 call_debugging(Topic,Goal) :- setup_call_cleanup(debug(Topic), Goal, nodebug(Topic)).
|
Daniel@0
|
151 call_nodebug(Goal) :-
|
Daniel@0
|
152 setup_call_cleanup( (setof(T,debugging(T),Topics),maplist(nodebug,Topics)), Goal, maplist(debug,Topics)).
|
Daniel@0
|
153
|
Daniel@0
|
154 view_computations :-
|
Daniel@0
|
155 call_debugging(computations(item),termutils:with_status_line(get_single_char(_))).
|
Daniel@0
|
156
|
Daniel@0
|
157 logging(dmlvis(method)).
|
Daniel@0
|
158 logging(dmlvis(perspective)).
|
Daniel@0
|
159 logging(log).
|
Daniel@0
|
160
|
Daniel@0
|
161 prolog:debug_print_hook(computations(item),Fmt,Args) :-
|
Daniel@0
|
162 termutils:status(Fmt,Args).
|
Daniel@0
|
163
|
Daniel@0
|
164 prolog:debug_print_hook(Topic,Fmt,Args) :-
|
Daniel@0
|
165 logging(Topic), log_stream(S),
|
Daniel@0
|
166 get_time(T),
|
Daniel@0
|
167 format(S,'~@ ~w | ~@\n',[format_time(current_output,'%FT%T',T), Topic, format(Fmt,Args)]),
|
Daniel@0
|
168 fail.
|
Daniel@0
|
169
|
Daniel@0
|
170 update(dml) :-
|
Daniel@0
|
171 debug(log,'Updating dml-cliopatria repository.',[]),
|
Daniel@0
|
172 shell('cd cpack/dml && hg pull && hg update'),
|
Daniel@0
|
173 make.
|
Daniel@0
|
174
|
Daniel@0
|
175 start_matlab :- start_matlab([]).
|
Daniel@0
|
176 start_matlab(Opts) :- mlserver:start_matlab([path([dml(matlab)])|Opts]).
|
Daniel@0
|
177 start_r_server :- real:r_start_server.
|
Daniel@0
|
178
|
Daniel@0
|
179 :- multifile sandbox:safe_primitive/1.
|
Daniel@0
|
180 :- multifile sandbox:safe_directive/1.
|
Daniel@0
|
181 sandbox:safe_primitive(dml_permissions:file_permission(_,_)).
|
Daniel@0
|
182 sandbox:safe_primitive(cp_audio:audio_link(_,_,_)).
|
Daniel@0
|
183
|
Daniel@0
|
184 initiate_bl_scraping(Status) :-
|
Daniel@0
|
185 format('% Initiating BL audio link scraping...\n',[]),
|
Daniel@0
|
186 async:async_memo(vis_cla, bl_p2r:scrape_all([],_), Status, [recompute(failed),status_var(time-progress(summary))]).
|
Daniel@0
|
187
|
Daniel@0
|
188 after_load :-
|
Daniel@0
|
189 warm_indices,
|
Daniel@0
|
190 initiate_bl_scraping(_),
|
Daniel@0
|
191 start_r_server,
|
Daniel@0
|
192 start_matlab.
|