View source with formatted comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker, Michiel Hildebrand
    4    E-mail:        J.Wielemaker@uva.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2010-2014, University of Amsterdam
    7                              VU University Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(javascript,
   37          [ js_script//1,               % +Content
   38
   39            js_call//1,                 % +Function(Arg..)
   40            js_new//2,                  % +Id, +Function(+Args)
   41            js_expression//1,           % +Expression
   42            js_arg_list//1,             % +ListOfExpressions
   43            js_arg//1,                  % +Arg
   44            js_args//1,                 % +Args
   45
   46            javascript/4                % Quasi Quotation handler
   47          ]).   48
   49:- use_module(library(http/html_write)).   50:- use_module(library(http/json)).   51:- use_module(library(apply)).   52:- use_module(library(error)).   53:- use_module(library(lists)).   54:- use_module(library(debug)).   55:- use_module(library(quasi_quotations)).   56:- use_module(library(dcg/basics)).   57:- use_module(js_grammar).   58
   59:- html_meta
   60    js_script(html, ?, ?).   61
   62:- quasi_quotation_syntax(javascript).   63
   64/** <module> Utilities for including JavaScript
   65
   66This library is a supplement   to library(http/html_write) for producing
   67JavaScript fragments. Its main role is  to   be  able to call JavaScript
   68functions  with  valid  arguments  constructed  from  Prolog  data.  For
   69example, suppose you want to call a   JavaScript  functions to process a
   70list of names represented as Prolog atoms.   This  can be done using the
   71call below, while without this library you   would have to be careful to
   72properly escape special characters.
   73
   74    ==
   75    numbers_script(Names) -->
   76        html(script(type('text/javascript'),
   77             [ \js_call('ProcessNumbers'(Names)
   78             ]),
   79    ==
   80
   81The accepted arguments are described with js_expression//1.
   82*/
   83
   84%!  js_script(+Content)// is det.
   85%
   86%   Generate a JavaScript =script= element with the given content.
   87
   88js_script(Content) -->
   89    html(script(type('text/javascript'),
   90                Content)).
   91
   92
   93                 /*******************************
   94                 *        QUASI QUOTATION       *
   95                 *******************************/
   96
   97%!  javascript(+Content, +Vars, +VarDict, -DOM) is det.
   98%
   99%   Quasi quotation parser for JavaScript  that allows for embedding
  100%   Prolog variables to substitude _identifiers_   in the JavaScript
  101%   snippet. Parameterizing a JavaScript string   is  achieved using
  102%   the JavaScript `+` operator, which   results in concatenation at
  103%   the client side.
  104%
  105%     ==
  106%         ...,
  107%         js_script({|javascript(Id, Config)||
  108%                     $(document).ready(function() {
  109%                        $("#"+Id).tagit(Config);
  110%                      });
  111%                    |}),
  112%         ...
  113%     ==
  114%
  115%   The current implementation tokenizes the   JavaScript  input and
  116%   yields syntax errors on unterminated  comments, strings, etc. No
  117%   further parsing is  implemented,  which   makes  it  possible to
  118%   produce syntactically incorrect and   partial JavaScript. Future
  119%   versions are likely to include a  full parser, generating syntax
  120%   errors.
  121%
  122%   The parser produces a  term  `\List`,   which  is  suitable  for
  123%   js_script//1 and html//1.  Embedded  variables   are  mapped  to
  124%   `\js_expression(Var)`, while the remaining  text   is  mapped to
  125%   atoms.
  126%
  127%   @tbd    Implement a full JavaScript parser. Users should _not_
  128%           rely on the ability to generate partial JavaScript
  129%           snippets.
  130
  131javascript(Content, Vars, Dict, \Parts) :-
  132    include(qq_var(Vars), Dict, QQDict),
  133    phrase_from_quasi_quotation(
  134        js(QQDict, Parts),
  135        Content).
  136
  137qq_var(Vars, _=Var) :-
  138    member(V, Vars),
  139    V == Var,
  140    !.
  141
  142js(Dict, [Pre, Subst|More]) -->
  143    here(Here0),
  144    js_tokens(_),
  145    here(Here1),
  146    js_token(identifier(Name)),
  147    { memberchk(Name=Var, Dict),
  148      !,
  149      Subst = \js_expression(Var),
  150      diff_to_atom(Here0, Here1, Pre)
  151    },
  152    js(Dict, More).
  153js(_, [Last]) -->
  154    string(Codes),
  155    \+ [_],
  156    !,
  157    { atom_codes(Last, Codes) }.
  158
  159js_tokens([]) --> [].
  160js_tokens([H|T]) -->
  161    js_token(H),
  162    js_tokens(T).
  163
  164
  165%       diff_to_atom(+Start, +End, -Atom)
  166%
  167%       True when Atom is an atom that represents the characters between
  168%       Start and End, where End must be in the tail of the list Start.
  169
  170diff_to_atom(Start, End, Atom) :-
  171    diff_list(Start, End, List),
  172    atom_codes(Atom, List).
  173
  174diff_list(Start, End, List) :-
  175    Start == End,
  176    !,
  177    List = [].
  178diff_list([H|Start], End, [H|List]) :-
  179    diff_list(Start, End, List).
  180
  181here(Here, Here, Here).
  182
  183
  184                 /*******************************
  185                 *     PROLOG --> JAVASCRIPT    *
  186                 *******************************/
  187
  188%!  js_call(+Term)// is det.
  189%
  190%   Emit a call to a Javascript function.  The Prolog functor is the
  191%   name of the function. The arguments are converted from Prolog to
  192%   JavaScript using js_arg_list//1. Please not that Prolog functors can
  193%   be quoted atom and thus the following is legal:
  194%
  195%       ==
  196%           ...
  197%           html(script(type('text/javascript'),
  198%                [ \js_call('x.y.z'(hello, 42)
  199%                ]),
  200%       ==
  201
  202js_call(Term) -->
  203    { Term =.. [Function|Args] },
  204    html(Function), js_arg_list(Args), [';\n'].
  205
  206
  207%!  js_new(+Id, +Term)// is det.
  208%
  209%   Emit a call to a Javascript object declaration. This is the same
  210%   as:
  211%
  212%       ==
  213%       ['var ', Id, ' = new ', \js_call(Term)]
  214%       ==
  215
  216
  217js_new(Id, Term) -->
  218    { Term =.. [Function|Args] },
  219    html(['var ', Id, ' = new ', Function]), js_arg_list(Args), [';\n'].
  220
  221%!  js_arg_list(+Expressions:list)// is det.
  222%
  223%   Write javascript (function) arguments.  This   writes  "(", Arg,
  224%   ..., ")".  See js_expression//1 for valid argument values.
  225
  226
  227js_arg_list(Args) -->
  228    ['('], js_args(Args), [')'].
  229
  230js_args([]) -->
  231    [].
  232js_args([H|T]) -->
  233    js_expression(H),
  234    (   { T == [] }
  235    ->  []
  236    ;   html(', '),
  237        js_args(T)
  238    ).
  239
  240%!  js_expression(+Expression)// is det.
  241%
  242%   Emit a single JSON argument.  Expression is one of:
  243%
  244%       $ Variable :
  245%       Emitted as Javascript =null=
  246%       $ List :
  247%       Produces a Javascript list, where each element is processed
  248%       by this library.
  249%       $ object(Attributes) :
  250%       Where Attributes is a Key-Value list where each pair can be
  251%       written as Key-Value, Key=Value or Key(Value), accomodating
  252%       all common constructs for this used in Prolog.
  253%       $ { K:V, ... }
  254%       Same as object(Attributes), providing a more JavaScript-like
  255%       syntax.  This may be useful if the object appears literally
  256%       in the source-code, but is generally less friendlyto produce
  257%       as a result from a computation.
  258%       $ Dict :
  259%       Emit a dict as a JSON object using json_write_dict/3.
  260%       $ json(Term) :
  261%       Emits a term using json_write/3.
  262%       $ @(Atom) :
  263%       Emits these constants without quotes.  Normally used for the
  264%       symbols =true=, =false= and =null=, but can also be use for
  265%       emitting JavaScript symbols (i.e. function- or variable
  266%       names).
  267%       $ Number :
  268%       Emited literally
  269%       $ symbol(Atom) :
  270%       Synonym for @(Atom).  Deprecated.
  271%       $ Atom or String :
  272%       Emitted as quoted JavaScript string.
  273
  274js_expression(Expr) -->
  275    js_arg(Expr),
  276    !.
  277js_expression(Expr) -->
  278    { type_error(js(expression), Expr) }.
  279
  280%!  js_arg(+Expression)// is semidet.
  281%
  282%   Same as js_expression//1, but fails if Expression is invalid,
  283%   where js_expression//1 raises an error.
  284%
  285%   @deprecated     New code should use js_expression//1.
  286
  287js_arg(H) -->
  288    { var(H) },
  289    !,
  290    [null].
  291js_arg(object(H)) -->
  292    { is_list(H) },
  293    !,
  294    html([ '{', \js_kv_list(H), '}' ]).
  295js_arg({}(Attrs)) -->
  296    !,
  297    html([ '{', \js_kv_cslist(Attrs), '}' ]).
  298js_arg(@(Id)) --> js_identifier(Id).
  299js_arg(symbol(Id)) --> js_identifier(Id).
  300js_arg(json(Term)) -->
  301    { json_to_string(json(Term), String),
  302      debug(json_arg, '~w~n', String)
  303    },
  304    [ String ].
  305js_arg(Dict) -->
  306    { is_dict(Dict),
  307      !,
  308      with_output_to(string(String),
  309                     json_write_dict(current_output, Dict, [width(0)]))
  310    },
  311    [ String ].
  312js_arg(H) -->
  313    { is_list(H) },
  314    !,
  315    html([ '[', \js_args(H), ']' ]).
  316js_arg(H) -->
  317    { number(H) },
  318    !,
  319    [H].
  320js_arg(H) -->
  321    { atomic(H),
  322      !,
  323      js_quoted_string(H, Q)
  324    },
  325    [ '"', Q, '"'
  326    ].
  327
  328js_kv_list([]) --> [].
  329js_kv_list([H|T]) -->
  330    (   js_kv(H)
  331    ->  (   { T == [] }
  332        ->  []
  333        ;   html(', '),
  334            js_kv_list(T)
  335        )
  336    ;   { type_error(javascript_key_value, H) }
  337    ).
  338
  339js_kv(Key:Value) -->
  340    !,
  341    js_key(Key), [:], js_expression(Value).
  342js_kv(Key-Value) -->
  343    !,
  344    js_key(Key), [:], js_expression(Value).
  345js_kv(Key=Value) -->
  346    !,
  347    js_key(Key), [:], js_expression(Value).
  348js_kv(Term) -->
  349    { compound(Term),
  350      Term =.. [Key,Value]
  351    },
  352    !,
  353    js_key(Key), [:], js_expression(Value).
  354
  355js_key(Key) -->
  356    (   { must_be(atom, Key),
  357          js_identifier(Key)
  358        }
  359    ->  [Key]
  360    ;   { js_quoted_string(Key, QKey) },
  361        html(['\'', QKey, '\''])
  362    ).
  363
  364js_kv_cslist((A,B)) -->
  365    !,
  366    js_kv(A),
  367    html(', '),
  368    js_kv_cslist(B).
  369js_kv_cslist(A) -->
  370    js_kv(A).
  371
  372%!  js_quoted_string(+Raw, -Quoted)
  373%
  374%   Quote text for use in JavaScript.  Quoted does _not_ include the
  375%   leading and trailing quotes.
  376%
  377%   @tbd    Join with json stuff.
  378
  379js_quoted_string(Raw, Quoted) :-
  380    atom_codes(Raw, Codes),
  381    phrase(js_quote_codes(Codes), QuotedCodes),
  382    atom_codes(Quoted, QuotedCodes).
  383
  384js_quote_codes([]) -->
  385    [].
  386js_quote_codes([0'\r,0'\n|T]) -->
  387    !,
  388    "\\n",
  389    js_quote_codes(T).
  390js_quote_codes([0'<,0'/|T]) -->        % Avoid XSS scripting hacks
  391    !,
  392    "<\\/",
  393    js_quote_codes(T).
  394js_quote_codes([H|T]) -->
  395    js_quote_code(H),
  396    js_quote_codes(T).
  397
  398js_quote_code(0'') -->
  399    !,
  400    "\\'".
  401js_quote_code(0'") -->
  402    !,
  403    "\\\"".
  404js_quote_code(0'\\) -->
  405    !,
  406    "\\\\".
  407js_quote_code(0'\n) -->
  408    !,
  409    "\\n".
  410js_quote_code(0'\r) -->
  411    !,
  412    "\\r".
  413js_quote_code(0'\t) -->
  414    !,
  415    "\\t".
  416js_quote_code(C) -->
  417    [C].
  418
  419%!  js_identifier(+Id:atom)// is det.
  420%
  421%   Emit an identifier if it is a valid one
  422
  423js_identifier(Id) -->
  424    { must_be(atom, Id),
  425      js_identifier(Id)
  426    },
  427    !,
  428    [ Id ].
  429js_identifier(Id) -->
  430    { domain_error(js(identifier), Id)
  431    }.
  432
  433%!  js_identifier(+Id:atom) is semidet.
  434%
  435%   True if Id is a  valid   identifier.  In traditional JavaScript,
  436%   this means it starts  with  [$_:letter:]   and  is  followed  by
  437%   [$_:letter:digit:]
  438
  439js_identifier(Id) :-
  440    sub_atom(Id, 0, 1, _, First),
  441    char_type(First, csymf),
  442    forall(sub_atom(Id, _, 1, _, Char), char_type(Char, csym)).
  443
  444
  445%!  json_to_string(+JSONTerm, -String)
  446%
  447%   Write JSONTerm to String.
  448
  449json_to_string(JSON, String) :-
  450    with_output_to(string(String),
  451                   json_write(current_output,JSON,[width(0)]))