View source with raw comments or as raw
   1/*  Part of SWI-Prolog
   2
   3    Author:        Jan Wielemaker
   4    E-mail:        J.Wielemaker@vu.nl
   5    WWW:           http://www.swi-prolog.org
   6    Copyright (c)  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(http_multipart_plugin,
  37          [
  38          ]).
  39:- use_module(http_stream).
  40:- use_module(http_header).
  41:- use_module(library(debug)).
  42:- use_module(library(option)).
  43
  44/** <module> Multipart form-data plugin
  45
  46This plugin for library(http_client)   automatically translates messages
  47with content-type =|multipart/form-data|= into a list   of  Name = Value
  48pairs, greatly simplifying the processing of   forms  with this type.
  49
  50After loading this plugin, multipart form-data   can be accessed through
  51http_parameters/3 from library(http/http_parameters) or http_read_data/3
  52from library(http/http_client).
  53*/
  54
  55:- multifile
  56    http_client:http_convert_data/4,
  57    http_parameters:form_data_content_type/1.
  58
  59%!  http_client:http_convert_data(+In, +Fields, -Data, +Options) is semidet.
  60%
  61%   Convert =|multipart/form-data|= messages for http_read_data/3.
  62%   This plugin adds the folling options to http_read_data/3:
  63%
  64%     * form_data(+AsForm)
  65%     If the content-type is =|multipart/form-data|=, return the
  66%     form-data either in one of the following formats:
  67%
  68%       - AsForm = form
  69%       A list of Name=Value, where Value is an atom.
  70%       - AsForm = mime
  71%       A list of mime(Properties, Value, []).  This is a backward
  72%       compatibility mode, emulating library(http/http_mime_plugin).
  73%       Note that if the disposition contains a =filename=
  74%       property, the data is read as binary unless there is a
  75%       charset parameter in the Content-Type stating otherwise,
  76%       while the old library would use UTF-8 for text files.
  77%
  78%     * input_encoding(+Encoding)
  79%     Encoding to be used for parts that have no =filename=
  80%     disposition and no Content-Type with a charset indication.
  81%     This is typically the case for input widgets and browsers
  82%     encode this using the encoding of the page. As the SWI-Prolog
  83%     http library emits pages in UTF-8, the default is =utf8=.
  84%
  85%     * on_filename(:CallBack)
  86%     If a part with a =filename= disposition is found and this
  87%     option is given, call CallBack as below.  `Stream` is the
  88%     multipart input stream, which has octet (raw) encoding.
  89%     `Value` is returned as result.  Note that the callback
  90%     may wish to save the result into a file and return e.g.,
  91%     file(Path) to indicate where the file was saved.
  92%
  93%         call(:CallBack, +Stream, -Value, +Options).
  94%
  95%     The Options list contains information from the part header.
  96%     It always contains name(Name) and filename(FileName).  It
  97%     may contain a term media(Type/SubType, Params) if the part
  98%     contains a Content-Type header.
  99
 100http_client:http_convert_data(In, Fields, Data, Options) :-
 101    memberchk(content_type(Type), Fields),
 102    multipart_type(Type, Boundary),
 103    !,
 104    setup_call_cleanup(
 105        multipart_open(In, Stream, [boundary(Boundary)]),
 106        process_parts(Stream, Data, Options),
 107        close(Stream)).
 108
 109%!  multipart_type(+Type, -Boundary) is semidet.
 110%
 111%   True   if   Type   is   of   the   form   =|multipart/form-data;
 112%   boundary="..."|=  and  Boundary  is  a   string  describing  the
 113%   boundary.
 114
 115multipart_type(Type, Boundary) :-
 116    http_parse_header_value(content_type, Type,
 117                            media(multipart/'form-data', Params)),
 118    memberchk(boundary=Boundary, Params).
 119
 120
 121process_parts(Stream, [Part|More], Options) :-
 122    http_read_header(Stream, HTTPHeader),
 123    part_header(HTTPHeader, Params, Name, Encoding),
 124    part_value(Stream, Name, Params, Encoding, Part, Options),
 125    debug(multipart(content), 'Got ~q~n', [Part]),
 126    (   multipart_open_next(Stream)
 127    ->  process_parts(Stream, More, Options)
 128    ;   More = []
 129    ).
 130
 131set_encoding(text, Stream, _) :-
 132    !,
 133    (   set_stream(Stream, encoding(bom))
 134    ->  stream_property(Stream, encoding(Enc)),
 135        debug(multipart(bom), 'BOM: ~q', [Enc])
 136    ;   set_stream(Stream, encoding(iso_latin_1)) % RFC2616, sec. 3.7.1
 137    ).
 138set_encoding(input, Stream, Options) :-
 139    !,
 140    option(input_encoding(Enc), Options, utf8),
 141    set_stream(Stream, encoding(Enc)).
 142set_encoding(Enc, Stream, _) :-
 143    set_stream(Stream, encoding(Enc)).
 144
 145
 146%!  part_header(+PartHeader, -Params, -Name, -Encoding) is det.
 147%
 148%   Extract the form-field Name, the   content Encoding and possible
 149%   other properties of the form-field.  Extra properties are:
 150%
 151%     - filename(Name)
 152%     - media(Type/SubType, MediaParams)
 153
 154part_header(PartHeader, Extra, Name, Encoding) :-
 155    memberchk(content_disposition(disposition('form-data', DProps)),
 156              PartHeader),
 157    memberchk(name=Name, DProps),
 158    (   filename(DProps, Extra, Extra1)
 159    ->  part_encoding(PartHeader, Extra1, Encoding)
 160    ;   Encoding = input,
 161        Extra = []
 162    ).
 163
 164filename(DProps, Extra, Tail) :-
 165    memberchk(filename=FileName, DProps),
 166    !,
 167    Extra = [filename(FileName)|Tail].
 168
 169part_encoding(PartHeader, Extra, Encoding) :-
 170    memberchk(content_type(TypeA), PartHeader),
 171    http_parse_header_value(content_type, TypeA, MediaType),
 172    !,
 173    Extra = [MediaType],
 174    media_type_encoding(MediaType, Encoding).
 175
 176media_type_encoding(media(_Type, Params), Encoding) :-
 177    memberchk(charset=CharSet, Params),
 178    charset_encoding(CharSet, Encoding).
 179media_type_encoding(media(Type/SubType, _Params), Encoding) :-
 180    media_encoding(Type, SubType, Encoding).
 181
 182charset_encoding(CharSet, utf8) :-
 183    sub_atom_icasechk(CharSet, _, 'utf-8'),
 184    !.
 185charset_encoding(_, octet).
 186
 187media_encoding(text, _, text) :- !.
 188media_encoding(_,    _, octet).
 189
 190
 191%!  part_value(+Stream, +Name, +Params, +Encoding, -Part, +Options)
 192
 193part_value(Stream, Name, Params, Encoding, Part, Options) :-
 194    option(form_data(mime), Options),
 195    !,
 196    set_encoding(Encoding, Stream, Options),
 197    Part = mime([disposition('form-data'),name(Name)|Properties], Atom, []),
 198    mime_properties(Params, Properties),
 199    read_string(Stream, _, String),
 200    atom_string(Atom, String).
 201part_value(Stream, Name, Params, _, Name=Value, Options) :-
 202    memberchk(filename(_), Params),
 203    option(on_filename(Goal), Options),
 204    !,
 205    call(Goal, Stream, Value, [name(Name)|Params]).
 206part_value(Stream, Name, _, Encoding, Name=Value, Options) :-
 207    set_encoding(Encoding, Stream, Options),
 208    read_string(Stream, _, String),
 209    atom_string(Value, String).
 210
 211mime_properties([], []).
 212mime_properties([media(Type/SubType, Params)|T0],
 213                [type(ContentType)|T]) :-
 214    !,
 215    atomic_list_concat([Type, SubType], /, ContentType),
 216    (   memberchk(charset(CharSet), Params)
 217    ->  T = [character_set(CharSet)|T1]
 218    ;   T = T1
 219    ),
 220    mime_properties(T0, T1).
 221mime_properties([H|T0], [H|T]) :-
 222    mime_properties(T0, T).
 223
 224
 225http_parameters:form_data_content_type(ContentType) :-
 226    sub_atom(ContentType, 0, _, _, 'multipart/form-data').