1:- module(st_funs, [
    2    encode_path/2,        % +Path, -Encoded
    3    encode_query_value/2, % +QueryValue, -Encoded
    4    encode_fragment/2     % +Fragment, -Encoded
    5]).

Predefined functions

Defines various helper functions to work with templates, HTML and otherwise. */

   13:- use_module(library(uri)).   14:- use_module(st_expr).   15
   16% Function to encode URL paths.
   17
   18:- st_set_function(encode_path, 1, encode_path).
 encode_path(+Path, -Encoded) is det
Implements function to encode the path value of an URI. See uri_encoded/3.
   25encode_path(Path, Encoded):-
   26    uri_encoded(path, Path, Encoded).
   27
   28% Function to encode URL query.
   29
   30:- st_set_function(encode_query_value, 1, encode_query_value).
 encode_query_value(+QueryValue, -Encoded) is det
Implements function to encode the query value of an URI. See uri_encoded/3.
   37encode_query_value(Value, Encoded):-
   38    uri_encoded(query_value, Value, Encoded).
   39
   40% Function to encode URL fragment.
   41
   42:- st_set_function(encode_fragment, 1, encode_fragment).
 encode_fragment(+Fragment, -Encoded) is det
Implements function to encode the fragment of an URI. See uri_encoded/3.
   49encode_fragment(Fragment, Encoded):-
   50    uri_encoded(fragment, Fragment, Encoded)