36
   37:- module(web_storage,
   38          [ storage_file/1,                        39            storage_file_extension/2,              40            storage_file_extension_head/3,         41            storage_file/3,                        42            storage_meta_data/2,                   43            storage_meta_property/2,               44            storage_commit/2,                      45
   46            storage_fsck/0,
   47            storage_repack/0,
   48            storage_repack/1,                      49            storage_unpack/0,
   50
   51            storage_store_term/2,                  52            storage_load_term/2,                   53
   54            use_gitty_file/1,                      55            use_gitty_file/2                       56          ]).   57:- use_module(library(http/http_dispatch)).   58:- use_module(library(http/http_parameters)).   59:- use_module(library(http/http_json)).   60:- use_module(library(http/http_cors)).   61:- use_module(library(http/mimetype)).   62:- use_module(library(lists)).   63:- use_module(library(settings)).   64:- use_module(library(random)).   65:- use_module(library(apply)).   66:- use_module(library(option)).   67:- use_module(library(debug)).   68:- use_module(library(broadcast)).   69:- use_module(library(readutil)).   70:- use_module(library(solution_sequences)).   71:- use_module(library(dcg/basics)).   72:- use_module(library(pcre)).   73:- use_module(library(pengines_io)).   74
   75:- use_module(page).   76:- use_module(gitty).   77:- use_module(patch).   78:- use_module(config).   79:- use_module(search).   80:- use_module(authenticate).   81:- use_module(pep).   82
   83:- meta_predicate
   84    use_gitty_file(:),
   85    use_gitty_file(:, +).   86
   87:- multifile
   88    search_sources_hook/2,                         89    typeahead_hooked/1.                            90
   98
   99:- setting(directory, callable, data(storage),
  100           'The directory for storing files.').  101
  102:- http_handler(swish('p/'),
  103                web_storage,
  104                [ id(web_storage), prefix ]).  105:- http_handler(swish('source_list'),
  106                source_list,
  107                [ id(source_list) ]).  108:- http_handler(swish('source_modified'),
  109                source_modified,
  110                [ id(source_modified) ]).  111
  112:- listen(http(pre_server_start),
  113          open_gittystore(_)).  114
  115:- dynamic  storage_dir/1.  116:- volatile storage_dir/1.  117
  118open_gittystore(Dir0) :-
  119    storage_dir(Dir),
  120    !,
  121    Dir = Dir0.
  122open_gittystore(Dir) :-
  123    with_mutex(web_storage, open_gittystore_guarded(Dir0)),
  124    Dir = Dir0.
  125
  126open_gittystore_guarded(Dir) :-
  127    storage_dir(Dir),
  128    !.
  129open_gittystore_guarded(Dir) :-
  130    setting(directory, Spec),
  131    absolute_file_name(Spec, Dir,
  132                       [ file_type(directory),
  133                         access(write),
  134                         file_errors(fail)
  135                       ]),
  136    !,
  137    gitty_open_options(Options),
  138    gitty_open(Dir, Options),
  139    asserta(storage_dir(Dir)).
  140open_gittystore_guarded(Dir) :-
  141    setting(directory, Spec),
  142    absolute_file_name(Spec, Dir,
  143                       [ solutions(all)
  144                       ]),
  145    \+ exists_directory(Dir),
  146    create_store(Dir),
  147    !,
  148    gitty_open_options(Options),
  149    gitty_open(Dir, Options),
  150    asserta(storage_dir(Dir)).
  151
  152create_store(Dir) :-
  153    exists_directory('storage/ref'),
  154    !,
  155    print_message(informational, moved_old_store(storage, Dir)),
  156    rename_file(storage, Dir).
  157create_store(Dir) :-
  158    catch(make_directory(Dir),
  159          error(permission_error(create, directory, Dir), _),
  160          fail),
  161    !.
  162
  163gitty_open_options(Options) :-
  164    findall(Opt, gitty_open_option(Opt), Options).
  165
  166gitty_open_option(Option) :-
  167    swish_config(redis, DB),
  168    !,
  169    (   Option = redis(DB)
  170    ;   gitty_redis_option(Option)
  171    ).
  172
  173gitty_redis_option(redis_prefix(Prefix)) :-
  174    swish_config(redis_prefix, Prefix).
  175gitty_redis_option(redis_ro(Server)) :-
  176    swish_config(redis_ro, Server).
  177
  184
  185web_storage(Request) :-
  186    memberchk(method(options), Request),
  187    !,
  188    cors_enable(Request,
  189                [ methods([get,post,put,delete])
  190                ]),
  191    format('~n').
  192web_storage(Request) :-
  193    cors_enable(Request,
  194                [ methods([get,post,put,delete])
  195                ]),
  196    authenticate(Request, Auth),
  197    option(method(Method), Request),
  198    open_gittystore(_),
  199    storage(Method, Request, [identity(Auth)]).
  200
  201:- multifile
  202    swish_config:authenticate/2,
  203    swish_config:chat_count_about/2,
  204    swish_config:user_profile/2.              205
  206storage(get, Request, Options) :-
  207    http_parameters(Request,
  208                    [ format(Fmt,  [ oneof([swish,raw,json,history,diff]),
  209                                     default(swish),
  210                                     description('How to render')
  211                                   ]),
  212                      depth(Depth, [ default(5),
  213                                     integer,
  214                                     description('History depth')
  215                                   ]),
  216                      to(RelTo,    [ optional(true),
  217                                     description('Diff relative to')
  218                                   ])
  219                    ]),
  220    (   Fmt == history
  221    ->  (   nonvar(RelTo)
  222        ->  Format = history(Depth, RelTo)
  223        ;   Format = history(Depth)
  224        )
  225    ;   Fmt == diff
  226    ->  Format = diff(RelTo)
  227    ;   Format = Fmt
  228    ),
  229    storage_get(Request, Format, Options).
  230
  231storage(post, Request, Options) :-
  232    http_read_json_dict(Request, Dict),
  233    option(data(Data), Dict, ""),
  234    option(type(Type), Dict, pl),
  235    storage_dir(Dir),
  236    meta_data(Dir, Dict, _, Meta, Options),
  237    (   atom_string(Base, Dict.get(meta).get(name))
  238    ->  file_name_extension(Base, Type, File),
  239        (   authorized(gitty(create(File,named,Meta)), Options),
  240            catch(gitty_create(Dir, File, Data, Meta, Commit),
  241                  error(gitty(file_exists(File)),_),
  242                  fail)
  243        ->  true
  244        ;   Error = json{error:file_exists,
  245                         file:File}
  246        )
  247    ;   (   repeat,
  248            random_filename(Base),
  249            file_name_extension(Base, Type, File),
  250            authorized(gitty(create(File,random,Meta)), Options),
  251            catch(gitty_create(Dir, File, Data, Meta, Commit),
  252                  error(gitty(file_exists(File)),_),
  253                  fail)
  254        ->  true
  255        )
  256    ),
  257    (   var(Error)
  258    ->  debug(storage, 'Created: ~p', [Commit]),
  259        storage_url(File, URL),
  260
  261        broadcast(swish(created(File, Commit))),
  262        follow(Commit, Dict),
  263        reply_json_dict(json{url:URL,
  264                             file:File,
  265                             meta:Commit.put(symbolic, "HEAD")
  266                            })
  267    ;   reply_json_dict(Error)
  268    ).
  269storage(put, Request, Options) :-
  270    http_read_json_dict(Request, Dict),
  271    storage_dir(Dir),
  272    request_file(Request, Dir, File),
  273    (   Dict.get(update) == "meta-data"
  274    ->  gitty_data(Dir, File, Data, _OldMeta)
  275    ;   writeable(File)
  276    ->  option(data(Data), Dict, "")
  277    ;   option(path(Path), Request),
  278        throw(http_reply(forbidden(Path)))
  279    ),
  280    meta_data(Dir, Dict, PrevMeta, Meta, Options),
  281    storage_url(File, URL),
  282    authorized(gitty(update(File,PrevMeta,Meta)), Options),
  283    catch(gitty_update(Dir, File, Data, Meta, Commit),
  284          Error,
  285          true),
  286    (   var(Error)
  287    ->  debug(storage, 'Updated: ~p', [Commit]),
  288        collect_messages_as_json(
  289            broadcast(swish(updated(File, Commit))),
  290            Messages),
  291        debug(gitty(load), 'Messages: ~p', [Messages]),
  292        follow(Commit, Dict),
  293        reply_json_dict(json{ url:URL,
  294                              file:File,
  295                              meta:Commit.put(symbolic, "HEAD"),
  296                              messages:Messages
  297                            })
  298    ;   update_error(Error, Dir, Data, File, URL)
  299    ).
  300storage(delete, Request, Options) :-
  301    storage_dir(Dir),
  302    meta_data(Dir, _{}, PrevMeta, Meta, Options),
  303    request_file(Request, Dir, File),
  304    authorized(gitty(delete(File,PrevMeta)), Options),
  305    gitty_update(Dir, File, "", Meta, Commit),
  306    broadcast(swish(deleted(File, Commit))),
  307    reply_json_dict(true).
  308
  309writeable(File) :-
  310    \+ file_name_extension(_, lnk, File).
  311
  316
  317update_error(error(gitty(commit_version(_, Head, Previous)), _),
  318             Dir, Data, File, URL) :-
  319    !,
  320    gitty_diff(Dir, Previous, Head, OtherEdit),
  321    gitty_diff(Dir, Previous, data(Data), MyEdits),
  322    Status0 = json{url:URL,
  323                   file:File,
  324                   error:edit_conflict,
  325                   edit:_{server:OtherEdit,
  326                          me:MyEdits}
  327                  },
  328    (   OtherDiff = OtherEdit.get(data)
  329    ->  PatchOptions = [status(_), stderr(_)],
  330        patch(Data, OtherDiff, Merged, PatchOptions),
  331        Status1 = Status0.put(merged, Merged),
  332        foldl(patch_status, PatchOptions, Status1, Status)
  333    ;   Status = Status0
  334    ),
  335    reply_json_dict(Status, [ status(409) ]).
  336update_error(Error, _Dir, _Data, _File, _URL) :-
  337    throw(Error).
  338
  339patch_status(status(exit(0)), Dict, Dict) :- !.
  340patch_status(status(exit(Status)), Dict, Dict.put(patch_status, Status)) :- !.
  341patch_status(status(killed(Signal)), Dict, Dict.put(patch_killed, Signal)) :- !.
  342patch_status(stderr(""), Dict, Dict) :- !.
  343patch_status(stderr(Errors), Dict, Dict.put(patch_errors, Errors)) :- !.
  344
  349
  350follow(Commit, Dict) :-
  351    Dict.get(meta).get(follow) == true,
  352    _{name:File, profile_id:ProfileID} :< Commit,
  353    !,
  354    atom_concat('gitty:', File, DocID),
  355    broadcast(swish(follow(DocID, ProfileID, [update,chat]))).
  356follow(_, _).
  357
  363
  364request_file(Request, Dir, File) :-
  365    option(path_info(File), Request),
  366    (   gitty_file(Dir, File, _Hash)
  367    ->  true
  368    ;   http_404([], Request)
  369    ).
  370
  371storage_url(File, HREF) :-
  372    http_link_to_id(web_storage, path_postfix(File), HREF).
  373
  384
  385meta_data(Dict, Meta, Options) :-
  386    option(identity(Auth), Options),
  387    (   _ = Auth.get(identity)
  388    ->  HasIdentity = true
  389    ;   HasIdentity = false
  390    ),
  391    filter_auth(Auth, Auth1),
  392    (   filter_meta(Dict.get(meta), HasIdentity, Meta1)
  393    ->  Meta = meta{}.put(Auth1).put(Meta1)
  394    ;   Meta = meta{}.put(Auth1)
  395    ).
  396
  397meta_data(Store, Dict, PrevMeta, Meta, Options) :-
  398    meta_data(Dict, Meta1, Options),
  399    (   atom_string(Previous, Dict.get(previous)),
  400        is_gitty_hash(Previous),
  401        gitty_commit(Store, Previous, PrevMeta)
  402    ->  Meta = Meta1.put(previous, Previous)
  403    ;   Meta = Meta1
  404    ).
  405
  406filter_meta(Dict0, HasID, Dict) :-
  407    dict_pairs(Dict0, Tag, Pairs0),
  408    filter_pairs(Pairs0, HasID, Pairs),
  409    dict_pairs(Dict, Tag, Pairs).
  410
  411filter_pairs([], _, []).
  412filter_pairs([K-V0|T0], HasID, [K-V|T]) :-
  413    meta_allowed(K, HasID, Type),
  414    filter_type(Type, V0, V),
  415    !,
  416    filter_pairs(T0, HasID, T).
  417filter_pairs([_|T0], HasID, T) :-
  418    filter_pairs(T0, HasID, T).
  419
  420meta_allowed(public,         _,     boolean).
  421meta_allowed(example,        _,     boolean).
  422meta_allowed(author,         _,     string).
  423meta_allowed(avatar,         false, string).
  424meta_allowed(email,          _,     string).
  425meta_allowed(title,          _,     string).
  426meta_allowed(tags,           _,     list(string)).
  427meta_allowed(description,    _,     string).
  428meta_allowed(commit_message, _,     string).
  429meta_allowed(modify,         _,     list(atom)).
  430
  431filter_type(Type, V, V) :-
  432    is_of_type(Type, V),
  433    !.
  434filter_type(list(Type), V0, V) :-
  435    is_list(V0),
  436    maplist(filter_type(Type), V0, V).
  437filter_type(atom, V0, V) :-
  438    atomic(V0),
  439    atom_string(V, V0).
  440
  441filter_auth(Auth0, Auth) :-
  442    auth_template(Auth),
  443    Auth :< Auth0,
  444    !.
  445filter_auth(Auth, Auth).
  446
  447auth_template(_{identity:_, profile_id:_}).
  448auth_template(_{profile_id:_}).
  449auth_template(_{identity:_}).
  450
  451
  469
  470storage_get(Request, swish, Options) :-
  471    swish_reply_config(Request, Options),
  472    !.
  473storage_get(Request, Format, Options) :-
  474    storage_dir(Dir),
  475    request_file_or_hash(Request, Dir, FileOrHash, Type),
  476    Obj =.. [Type,FileOrHash],
  477    authorized(gitty(download(Obj, Format)), Options),
  478    storage_get(Format, Dir, Type, FileOrHash, Request),
  479    broadcast(swish(download(Dir, FileOrHash, Format))).
  480
  481storage_get(swish, Dir, Type, FileOrHash, Request) :-
  482    gitty_data_or_default(Dir, Type, FileOrHash, Code, Meta),
  483    chat_count(Meta, Count),
  484    swish_show([ code(Code),
  485                 file(FileOrHash),
  486                 st_type(gitty),
  487                 meta(Meta),
  488                 chat_count(Count)
  489               ],
  490               Request).
  491storage_get(raw, Dir, Type, FileOrHash, _Request) :-
  492    gitty_data_or_default(Dir, Type, FileOrHash, Code, Meta),
  493    file_mime_type(Meta.name, MIME),
  494    format('Content-type: ~w~n~n', [MIME]),
  495    format('~s', [Code]).
  496storage_get(json, Dir, Type, FileOrHash, _Request) :-
  497    gitty_data_or_default(Dir, Type, FileOrHash, Code, Meta),
  498    chat_count(Meta, Count),
  499    JSON0 = json{data:Code, meta:Meta, chats:_{total:Count}},
  500    (   open_hook(json, JSON0, JSON)
  501    ->  true
  502    ;   JSON = JSON0
  503    ),
  504    reply_json_dict(JSON).
  505storage_get(history(Depth, Includes), Dir, _, File, _Request) :-
  506    gitty_history(Dir, File, History, [depth(Depth),includes(Includes)]),
  507    reply_json_dict(History).
  508storage_get(history(Depth), Dir, _, File, _Request) :-
  509    gitty_history(Dir, File, History, [depth(Depth)]),
  510    reply_json_dict(History).
  511storage_get(diff(RelTo), Dir, _, File, _Request) :-
  512    gitty_diff(Dir, RelTo, File, Diff),
  513    reply_json_dict(Diff).
  514
  515request_file_or_hash(Request, Dir, FileOrHash, Type) :-
  516    option(path_info(FileOrHash), Request),
  517    (   gitty_file(Dir, FileOrHash, _Hash)
  518    ->  Type = file
  519    ;   is_gitty_hash(FileOrHash)
  520    ->  Type = hash
  521    ;   gitty_default_file(FileOrHash, _)
  522    ->  Type = default
  523    ;   http_404([], Request)
  524    ).
  525
  530
  531gitty_data_or_default(_, default, File, Code,
  532                      meta{name:File,
  533                           modify:[login,owner],
  534                           default:true,
  535                           chat:"large"
  536                          }) :-
  537    !,
  538    gitty_default_file(File, Path),
  539    read_file_to_string(Path, Code, []).
  540gitty_data_or_default(Dir, _, FileOrHash, Code, Meta) :-
  541    gitty_data(Dir, FileOrHash, Code, Meta),
  542    !.
  543
  544gitty_default_file(File, Path) :-
  545    file_name_extension(Base, Ext, File),
  546    memberchk(Ext, [pl,swinb]),
  547    forall(sub_atom(Base, _, 1, _, C),
  548           char_type(C, csym)),
  549    absolute_file_name(config(gitty/File), Path,
  550                       [ access(read),
  551                         file_errors(fail)
  552                       ]).
  553
  554
  559
  560chat_count(Meta, Chats) :-
  561    atom_concat('gitty:', Meta.get(name), DocID),
  562    swish_config:chat_count_about(DocID, Chats),
  563    !.
  564chat_count(_, 0).
  565
  566
  570
  571random_filename(Name) :-
  572    length(Chars, 8),
  573    maplist(random_char, Chars),
  574    atom_chars(Name, Chars).
  575
  576from('abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ').
  577
  578random_char(Char) :-
  579    from(From),
  580    atom_length(From, Len),
  581    Max is Len - 1,
  582    random_between(0, Max, I),
  583    sub_atom(From, I, 1, _, Char).
  584
  585
  590
  591:- multifile open_hook/3.  592
  593swish_show(Options0, Request) :-
  594    open_hook(swish, Options0, Options),
  595    !,
  596    swish_reply(Options, Request).
  597swish_show(Options, Request) :-
  598    swish_reply(Options, Request).
  599
  600
  601                   604
  615
  616storage_file(File) :-
  617    storage_file_extension(File, _).
  618
  619storage_file_extension(File, Ext) :-
  620    storage_file_extension_head(File, Ext, _).
  621
  622storage_file_extension_head(File, Ext, Head) :-
  623    open_gittystore(Dir),
  624    gitty_file(Dir, File, Ext, Head).
  625
  626storage_file(File, Data, Meta) :-
  627    open_gittystore(Dir),
  628    (   var(File)
  629    ->  gitty_file(Dir, File, Head),
  630        gitty_data(Dir, Head, Data, Meta)
  631    ;   gitty_data(Dir, File, Data, Meta)
  632    ).
  633
  634storage_meta_data(File, Meta) :-
  635    open_gittystore(Dir),
  636    (   var(File)
  637    ->  gitty_file(Dir, File, _Head)
  638    ;   true
  639    ),
  640    gitty_commit(Dir, File, Meta).
  641
  646
  647storage_commit(Hash, Meta) :-
  648    open_gittystore(Dir),
  649    gitty_plain_commit(Dir, Hash, Meta).
  650
  658
  659storage_meta_property(Meta, Property) :-
  660    current_meta_property(Property, How),
  661    meta_property(Property, How, Meta).
  662
  663meta_property(Property, dict, Identity) :-
  664    Property =.. [Name,Value],
  665    Value = Identity.get(Name).
  666meta_property(modify(Modify), _, Meta) :-
  667    (   Modify0 = Meta.get(modify)
  668    ->  Modify = Modify0
  669    ;   Modify = [any,login,owner]
  670    ).
  671
  672current_meta_property(peer(_Atom),       dict).
  673current_meta_property(public(_Bool),     dict).
  674current_meta_property(time(_Seconds),    dict).
  675current_meta_property(author(_String),   dict).
  676current_meta_property(identity(_String), dict).
  677current_meta_property(avatar(_String),   dict).
  678current_meta_property(modify(_List),     derived).
  679
  685
  686storage_store_term(Term, Hash) :-
  687    open_gittystore(Dir),
  688    with_output_to(string(S), write_canonical(Term)),
  689    gitty_save(Dir, S, term, Hash).
  690
  691storage_load_term(Hash, Term) :-
  692    open_gittystore(Dir),
  693    gitty_load(Dir, Hash, Data, term),
  694    term_string(Term, Data).
  695
  696
  697                   700
  709
  710use_gitty_file(File) :-
  711    use_gitty_file(File, []).
  712
  713use_gitty_file(M:Spec, Options) :-
  714    ensure_extension(Spec, pl, File),
  715    setup_watch(M:File, Options),
  716    storage_file(File, Data, Meta),
  717    atom_concat('swish://', File, URL),
  718    setup_call_cleanup(
  719        open_string(Data, In),
  720        load_files(M:URL,
  721                   [ stream(In),
  722                     modified(Meta.time),
  723                     if(changed)
  724                   | Options
  725                   ]),
  726        close(In)).
  727
  728ensure_extension(File, Ext, File) :-
  729    file_name_extension(_, Ext, File),
  730    !.
  731ensure_extension(Base, Ext, File) :-
  732    file_name_extension(Base, Ext, File).
  733
  734
  735:- dynamic
  736    watching/3.                                   737
  738setup_watch(M:File, Options) :-
  739    option(watch(true), Options, true),
  740    !,
  741    (   watching(File, M, Options)
  742    ->  true
  743    ;   retractall(watching(File, M, _)),
  744        assertz(watching(File, M, Options))
  745    ).
  746setup_watch(M:File, _Options) :-
  747    retractall(watching(File, M, _)).
  748
  749
  750                   753
  754:- initialization
  755    listen(swish(updated(File, Commit)),
  756       run_watchdog(File, Commit)).  757
  758run_watchdog(File, _Commit) :-
  759    debug(gitty(reload), 'File ~p was saved', [File]),
  760    forall(watching(File, Module, Options),
  761           use_gitty_file(Module:File, Options)).
  762
  763
  764                   767
  772
  773:- meta_predicate
  774    collect_messages_as_json(0, -).  775
  776:- thread_local
  777    messages/1.  778
  779collect_messages_as_json(Goal, Messages) :-
  780    retractall(messages(_)),
  781    setup_call_cleanup(
  782        asserta((user:thread_message_hook(Term,Kind,Lines) :-
  783                    collect_message(Term,Kind,Lines)),
  784                Ref),
  785        Goal,
  786        erase(Ref)),
  787    findall(Msg, retract(messages(Msg)), Messages).
  788
  789collect_message(Term, Kind, Lines) :-
  790    message_to_json(Term, Kind, Lines, JSON),
  791    assertz(messages(JSON)).
  792
  793message_to_json(Term, Kind, Lines, JSON) :-
  794    message_to_string(Term, String),
  795    JSON0 = json{type: message,
  796                 kind: Kind,
  797                 data: [String]},
  798    add_html_message(Kind, Lines, JSON0, JSON1),
  799    (   source_location(File, Line)
  800    ->  JSON2 = JSON1.put(location, json{file:File, line:Line})
  801    ;   JSON2 = JSON1
  802    ),
  803    (   message_details(Term, JSON2, JSON)
  804    ->  true
  805    ;   JSON = JSON2
  806    ).
  807
  808message_details(error(syntax_error(_What),
  809                      file(File,Line,Offset,_CharPos)),
  810                JSON0, JSON) :-
  811    JSON = JSON0.put(location, json{file:File, line:Line, ch:Offset})
  812                .put(code, syntax_error).
  813message_details(load_file(Step), JSON0, JSON) :-
  814    functor(Step, Code, _),
  815    JSON = JSON0.put(code, Code).
  816
  818:- if(current_predicate(message_lines_to_html/3)).  819add_html_message(Kind, Lines, JSON0, JSON) :-
  820    atom_concat('msg-', Kind, Class),
  821    message_lines_to_html(Lines, [Class], HTML),
  822    JSON = JSON0.put(html, HTML).
  823:- else.  824add_html_message(_, _, JSON, JSON).
  825:- endif.  826
  827                   830
  834
  835storage_fsck :-
  836    open_gittystore(Dir),
  837    gitty_fsck(Dir).
  838
  845
  846:- multifile
  847    gitty_driver_files:repack_objects/2,
  848    gitty_driver_files:unpack_packs/1.  849
  850storage_repack :-
  851    storage_repack([]).
  852storage_repack(Options) :-
  853    open_gittystore(Dir),
  854    (   gitty_driver(Dir, files)
  855    ->  gitty_driver_files:repack_objects(Dir, Options)
  856    ;   print_message(informational, gitty(norepack(driver)))
  857    ).
  858
  864
  865storage_unpack :-
  866    open_gittystore(Dir),
  867    (   gitty_driver(Dir, files)
  868    ->  gitty_driver_files:unpack_packs(Dir)
  869    ;   print_message(informational, gitty(nounpack(driver)))
  870    ).
  871
  872
  873                   876
  877:- multifile
  878    swish_search:typeahead/4.         879
  892
  893swish_search:typeahead(file, Query, FileInfo, _Options) :-
  894    \+ typeahead_hooked(file),
  895    !,
  896    open_gittystore(Dir),
  897    gitty_file(Dir, File, Head),
  898    gitty_plain_commit(Dir, Head, Meta),
  899    Meta.get(public) == true,
  900    (   sub_atom(File, 0, _, _, Query)   901    ->  true
  902    ;   meta_match_query(Query, Meta)
  903    ->  true
  904    ),
  905    FileInfo = Meta.put(_{type:"store", file:File}).
  906
  907meta_match_query(Query, Meta) :-
  908    member(Tag, Meta.get(tags)),
  909    sub_atom(Tag, 0, _, _, Query).
  910meta_match_query(Query, Meta) :-
  911    sub_atom(Meta.get(author), 0, _, _, Query).
  912meta_match_query(Query, Meta) :-
  913    Title = Meta.get(title),
  914    sub_atom_icasechk(Title, Start, Query),
  915    (   Start =:= 0
  916    ->  true
  917    ;   Before is Start-1,
  918        sub_atom(Title, Before, 1, _, C),
  919        \+ char_type(C, csym)
  920    ).
  921
  922swish_search:typeahead(store_content, Query, FileInfo, Options) :-
  923    \+ typeahead_hooked(store_content),
  924    limit(25, search_store_content(Query, FileInfo, Options)).
  925
  926search_store_content(Query, FileInfo, Options) :-
  927    open_gittystore(Dir),
  928    gitty_file(Dir, File, Head),
  929    gitty_data(Dir, Head, Data, Meta),
  930    Meta.get(public) == true,
  931    limit(5, search_file(File, Meta, Data, Query, FileInfo, Options)).
  932
  933search_file(File, Meta, Data, Query, FileInfo, Options) :-
  934    split_string(Data, "\n", "\r", Lines),
  935    nth1(LineNo, Lines, Line),
  936    match(Line, Query, Options),
  937    FileInfo = Meta.put(_{type:"store", file:File,
  938                          line:LineNo, text:Line, query:Query
  939                         }).
  940
  941
  942                   945
  980
  981
  982source_list(Request) :-
  983    memberchk(method(options), Request),
  984    !,
  985    cors_enable(Request,
  986                [ methods([get,post])
  987                ]),
  988    format('~n').
  989source_list(Request) :-
  990    cors_enable,
  991    authenticate(Request, Auth),
  992    http_parameters(Request,
  993                    [ q(Q, [optional(true)]),
  994                      o(Order, [ oneof([time,name,author,type]),
  995                                 optional(true)
  996                               ]),
  997                      d(Dir, [ oneof([asc, desc]),
  998                               optional(true)
  999                             ]),
 1000                      offset(Offset, [integer, default(0)]),
 1001                      limit(Limit, [integer, default(10)]),
 1002                      display_name(DisplayName, [optional(true), string]),
 1003                      avatar(Avatar, [optional(true), string])
 1004                    ]),
 1005    bound(Auth.put(_{display_name:DisplayName, avatar:Avatar}), AuthEx),
 1006    last_modified(Modified),
 1007    parse_query(Q, Query),
 1008    ESQuery0 = #{ query_string:Q,
 1009                  query:Query,
 1010                  auth:AuthEx,
 1011                  limit:Limit, offset:Offset
 1012                },
 1013    add_ordering(Order, Dir, ESQuery0, ESQuery),
 1014    search_sources(ESQuery, Result),
 1015    (   _ = Result.get(error)
 1016    ->  reply_json_dict(Result, [status(500)])
 1017    ;   reply_json_dict(Result.put(#{offset:Offset, modified:Modified}))
 1018    ).
 1019
 1020add_ordering(Order, _Dir, Q, Q) :-
 1021    var(Order),
 1022    !.
 1023add_ordering(Order, Dir, Q0, Q) :-
 1024    var(Dir),
 1025    !,
 1026    order(Order, Field, Dir),
 1027    Q = Q0.put(_{order_by: Field, order: Dir}).
 1028add_ordering(Order, Dir, Q0, Q) :-
 1029    order(Order, Field, _),
 1030    Q = Q0.put(_{order_by: Field, order: Dir}).
 1031
 1032order(type,  ext,   asc) :- !.
 1033order(time,  time,  desc) :- !.
 1034order(Field, Field, asc).
 1035
 1080
 1081search_sources(Query, Result) :-
 1082    search_sources_hook(Query, Result),
 1083    !.
 1084search_sources(Q,
 1085               #{ matches:Sources,
 1086                  total:Count,
 1087                  cpu:CPU
 1088                }) :-
 1089    statistics(cputime, CPU0),
 1090    findall(Source, source(Q.query, Q.auth, Source), AllSources),
 1091    statistics(cputime, CPU1),
 1092    length(AllSources, Count),
 1093    CPU is CPU1 - CPU0,
 1094    (   _{order_by:Field, order:Dir} :< Q
 1095    ->  order_cmp(Dir, Cmp),
 1096        sort(Field, Cmp, AllSources, Ordered)
 1097    ;   sort(time, @>=, AllSources, Ordered)
 1098    ),
 1099    list_offset_limit(Ordered, Q.offset, Q.limit, Sources).
 1100
 1101order_cmp(asc, @=<).
 1102order_cmp(desc, @>=).
 1103
 1104list_offset_limit(List0, Offset, Limit, List) :-
 1105    list_offset(List0, Offset, List1),
 1106    list_limit(List1, Limit, List).
 1107
 1108list_offset([_|T0], Offset, T) :-
 1109    succ(O1, Offset),
 1110    !,
 1111    list_offset(T0, O1, T).
 1112list_offset(List, _, List).
 1113
 1114list_limit([H|T0], Limit, [H|T]) :-
 1115    succ(L1, Limit),
 1116    !,
 1117    list_limit(T0, L1, T).
 1118list_limit(_, _, []).
 1119
 1120source(Query, Auth, Source) :-
 1121    source_q(Query, Auth, Source).
 1122
 1123source_q([user("me")], Auth, _Source) :-
 1124    \+ _ = Auth.get(avatar),
 1125    \+ user_property(Auth, identity(_Id)),
 1126    !,
 1127    fail.
 1128source_q(Query0, Auth, Source) :-
 1129    maplist(compile_query_element, Query0, Query),
 1130    type_constraint(Query, Query1, Type),
 1131    partition(content_query, Query1,
 1132              ContentConstraints, MetaConstraints),
 1133    storage_file_extension_head(File, Type, Head),
 1134    source_data(File, Head, Meta, Source),
 1135    visible(Meta, Auth, MetaConstraints),
 1136    maplist(matches_meta(Source, Auth), MetaConstraints),
 1137    matches_content(ContentConstraints, Head).
 1138
 1139compile_query_element(regex(String, Flags), Regex) =>
 1140    maplist(re_flag_option, Flags, Options),
 1141    re_compile(String, Regex, Options).
 1142compile_query_element(word(String), Regex) =>
 1143    re_compile(String, Regex,
 1144               [ extended(true),
 1145                 caseless(true)
 1146               ]).
 1147compile_query_element(type(String), Type) =>
 1148    Type = type(Atom),
 1149    atom_string(Atom, String).
 1150compile_query_element(TaggedRegex, QE),
 1151    TaggedRegex =.. [Tag,regex(String,Flags)] =>
 1152    maplist(re_flag_option, Flags, Options),
 1153    re_compile(String, Regex, Options),
 1154    QE =.. [Tag,Regex].
 1155compile_query_element(Any, QE) =>
 1156    QE = Any.
 1157
 1158re_flag_option(i, [caseless(true)]).
 1159re_flag_option(x, [extended(true)]).
 1160re_flag_option(m, [multiline(true)]).
 1161re_flag_option(s, [dotall(true)]).
 1162
 1163content_query(string(_)).
 1164content_query(regex(_)).
 1165
 1166source_data(File, Head, Meta, Source) :-
 1167    storage_commit(Head, Meta),
 1168    file_name_extension(_, Type, File),
 1169    Info = _{time:_, tags:_, author:_, avatar:_, name:_},
 1170    Info >:< Meta,
 1171    bound(Info, Info2),
 1172    Source = Info2.put(_{type:st_gitty, ext:Type}).
 1173
 1174bound(Dict0, Dict) :-
 1175    dict_pairs(Dict0, Tag, Pairs0),
 1176    include(bound, Pairs0, Pairs),
 1177    dict_pairs(Dict, Tag, Pairs).
 1178
 1179bound(_-V) :- nonvar(V).
 1180
 1182
 1183visible(Meta, Auth, Constraints) :-
 1184    memberchk(user("me"), Constraints),
 1185    !,
 1186    owns(Auth, Meta, user(_)).
 1187visible(Meta, _Auth, _Constraints) :-
 1188    Meta.get(public) == true,
 1189    !.
 1190visible(Meta, Auth, _Constraints) :-
 1191    owns(Auth, Meta, _).
 1192
 1201
 1202owns(Auth, Meta, user(me)) :-
 1203    storage_meta_property(Meta, identity(Id)),
 1204    !,
 1205    user_property(Auth, identity(Id)).
 1206owns(_Auth, Meta, _) :-                          1207    \+ Meta.get(public) == true,            1208    !,
 1209    fail.
 1210owns(Auth, Meta, user(avatar)) :-
 1211    storage_meta_property(Meta, avatar(Id)),
 1212    user_property(Auth, avatar(Id)),
 1213    !.
 1214owns(Auth, Meta, user(nickname)) :-
 1215    Auth.get(display_name) == Meta.get(author),
 1216    !.
 1217owns(Auth, Meta, host(How)) :-           1218    Peer = Auth.get(peer),
 1219    (   Peer == Meta.get(peer)
 1220    ->  How = same
 1221    ;   sub_atom(Meta.get(peer), 0, _, _, '127.0.0.')
 1222    ->  How = local
 1223    ).
 1224
 1228
 1229matches_meta(Dict, _, tag(Tag)) :-
 1230    !,
 1231    (   Tag == ""
 1232    ->  Dict.get(tags) \== []
 1233    ;   member(Tagged, Dict.get(tags)),
 1234        match_meta(Tag, Tagged)
 1235    ->  true
 1236    ).
 1237matches_meta(Dict, _, name(Name)) :-
 1238    !,
 1239    match_meta(Name, Dict.get(name)).
 1240matches_meta(Dict, _, user(Name)) :-
 1241    (   Name \== "me"
 1242    ->  match_meta(Name, Dict.get(author))
 1243    ;   true                 1244    ).
 1245
 1246match_meta(regex(RE), Value) :-
 1247    !,
 1248    re_match(RE, Value).
 1249match_meta(String, Value) :-
 1250    sub_atom_icasechk(Value, _, String).
 1251
 1252matches_content([], _) :- !.
 1253matches_content(Constraints, Hash) :-
 1254    storage_file(Hash, Data, _Meta),
 1255    maplist(match_content(Data), Constraints).
 1256
 1257match_content(Data, string(S)) :-
 1258    sub_atom_icasechk(Data, _, S),
 1259    !.
 1260match_content(Data, regex(RE)) :-
 1261    re_match(RE, Data).
 1262
 1267
 1268type_constraint(Query0, Query, Type) :-
 1269    partition(is_type, Query0, Types, Query),
 1270    (   Types == []
 1271    ->  true
 1272    ;   Types = [type(Type)]
 1273    ->  true
 1274    ;   maplist(arg(1), Types, List),
 1275        freeze(Type, memberchk(Type, List))
 1276    ).
 1277
 1278is_type(type(_)).
 1279
 1286
 1287parse_query(Q, Query) :-
 1288    var(Q),
 1289    !,
 1290    Query = [].
 1291parse_query(Q, Query) :-
 1292    string_codes(Q, Codes),
 1293    phrase(query(Query), Codes).
 1294
 1295query([H|T]) -->
 1296    blanks,
 1297    query1(H),
 1298    !,
 1299    query(T).
 1300query([]) -->
 1301    blanks.
 1302
 1303query1(Q) -->
 1304    tag(Tag, Value),
 1305    !,
 1306    {Q =.. [Tag,Value]}.
 1307query1(Q) -->
 1308    "\"", string(Codes), "\"",
 1309    !,
 1310    { string_codes(String, Codes),
 1311      Q = string(String)
 1312    }.
 1313query1(regex(String, Flags)) -->
 1314    "/", string(Codes), "/", re_flags(Flags),
 1315    !,
 1316    { string_codes(String, Codes)
 1317    }.
 1318query1(word(String)) -->
 1319    next_word(String),
 1320    { String \== ""
 1321    }.
 1322
 1323re_flags([H|T]) -->
 1324    re_flag(H),
 1325    !,
 1326    re_flags(T).
 1327re_flags([]) -->
 1328    blank.
 1329re_flags([]) -->
 1330    eos.
 1331
 1332re_flag(i) --> "i".
 1333re_flag(x) --> "x".
 1334re_flag(m) --> "m".
 1335re_flag(s) --> "s".
 1336
 1337next_word(String) -->
 1338    blanks, nonblank(H), string(Codes), ( blank ; eos ),
 1339    !,
 1340    { string_codes(String, [H|Codes]) }.
 1341
 1342tag(name, Value) --> "name:", tag_value(Value).
 1343tag(tag,  Value) --> "tag:",  tag_value(Value).
 1344tag(user, Value) --> "user:", tag_value(Value).
 1345tag(type, Value) --> "type:", tag_value(Value).
 1346
 1347tag_value(String) -->
 1348    blanks, "\"", !, string(Codes), "\"",
 1349    !,
 1350    { string_codes(String, Codes) }.
 1351tag_value(Q) -->
 1352    blanks, "/", string(Codes), "/", re_flags(Flags),
 1353    !,
 1354    {   Codes == []
 1355    ->  Q = ""
 1356    ;   string_codes(String, Codes),
 1357        Q = regex(String, Flags)
 1358    }.
 1359tag_value(String) -->
 1360    nonblank(H),
 1361    !,
 1362    string(Codes),
 1363    ( blank ; eos ),
 1364    !,
 1365    { string_codes(String, [H|Codes]) }.
 1366tag_value("") -->
 1367    "".
 1368
 1369                  1372
 1381
 1382source_modified(Request) :-
 1383    memberchk(method(options), Request),
 1384    !,
 1385    cors_enable(Request,
 1386                [ methods([get])
 1387                ]),
 1388    format('~n').
 1389source_modified(Request) :-
 1390    cors_enable,
 1391    authenticate(Request, _Auth),
 1392    last_modified(Time),
 1393    reply_json_dict(json{modified:Time}).
 1394
 1395:- dynamic gitty_last_modified/1. 1396
 1397update_last_modified(_,_) :-
 1398    with_mutex(gitty_last_modified,
 1399               update_last_modified_sync).
 1400
 1401update_last_modified_sync :-
 1402    get_time(Now),
 1403    retractall(gitty_last_modified(_)),
 1404    asserta(gitty_last_modified(Now)).
 1405
 1406last_modified(Time) :-
 1407    debugging(swish(sourcelist)),           1408    !,
 1409    get_time(Now),
 1410    Time is Now + 60.
 1411last_modified(Time) :-
 1412    with_mutex(gitty_last_modified,
 1413               last_modified_sync(Time)).
 1414
 1415last_modified_sync(Time) :-
 1416    (   gitty_last_modified(Time)
 1417    ->  true
 1418    ;   statistics(process_epoch, Time)
 1419    ).
 1420
 1421:- unlisten(swish(_)),
 1422   listen(swish(Event), notify_event(Event)). 1423
 1425notify_event(updated(File, Commit)) :-
 1426    atom_concat('gitty:', File, DocID),
 1427    update_last_modified(Commit, DocID).
 1428notify_event(deleted(File, Commit)) :-
 1429    atom_concat('gitty:', File, DocID),
 1430    update_last_modified(Commit, DocID).
 1431notify_event(created(File, Commit)) :-
 1432    atom_concat('gitty:', File, DocID),
 1433    update_last_modified(Commit, DocID).
 1434
 1435
 1436                  1439
 1440:- multifile prolog:message//1. 1441
 1442prolog:message(moved_old_store(Old, New)) -->
 1443    [ 'Moving SWISH file store from ~p to ~p'-[Old, New] ]