35
36:- module(mime_pack,
37 [ mime_pack/3 38 ]). 39:- use_module(mimetype). 40:- use_module(html_write). 41:- use_module(library(lists)). 42:- use_module(library(error)).
119mime_pack(Inputs, OutputStream, Boundary) :-
120 make_boundary(Inputs, Boundary),
121 pack_list(Inputs, OutputStream, Boundary).
122
123pack_list([], Out, Boundary) :-
124 format(Out, '--~w--\r\n', [Boundary]).
125pack_list([H|T], Out, Boundary) :-
126 format(Out, '--~w\r\n', [Boundary]),
127 pack(H, Out),
128 format(Out, '\r\n', []),
129 pack_list(T, Out, Boundary).
130
131pack(X, _Out) :-
132 var(X),
133 !,
134 instantiation_error(X).
135pack(Name=Value, Out) :-
136 !,
137 ( Value = file(FileName)
138 -> format(Out, 'Content-Disposition: form-data; name="~w"; filename="~w"\r\n',
139 [Name, FileName])
140 ; format(Out, 'Content-Disposition: form-data; name="~w"\r\n', [Name])
141 ),
142 pack(Value, Out).
143pack(html(HTML), Out) :-
144 format(Out, 'Content-Type: text/html\r\n\r\n', []),
145 print_html(Out, HTML).
146pack(file(File), Out) :-
147 !,
148 ( file_mime_type(File, Type)
149 -> true
150 ; Type = text/plain
151 ),
152 format(Out, 'Content-Type: ~w\r\n\r\n', [Type]),
153 ( Type = text/_
154 -> setup_call_cleanup(
155 open(File, read, In),
156 copy_stream_data(In, Out),
157 close(In))
158 ; stream_property(Out, encoding(OldEncoding)),
159 setup_call_cleanup(
160 set_stream(Out, encoding(octet)),
161 setup_call_cleanup(
162 open(File, read, In, [type(binary)]),
163 copy_stream_data(In, Out),
164 close(In)),
165 set_stream(Out, encoding(OldEncoding)))
166 ).
167pack(stream(In, Len), Out) :-
168 !,
169 format(Out, '\r\n', []),
170 copy_stream_data(In, Out, Len).
171pack(stream(In), Out) :-
172 !,
173 format(Out, '\r\n', []),
174 copy_stream_data(In, Out).
175pack(mime(Atts, Data, []), Out) :- 176 !,
177 write_mime_attributes(Atts, Out),
178 pack(Data, Out).
179pack(mime(_Atts, '', Parts), Out) :-
180 make_boundary(Parts, Boundary),
181 format('Content-type: multipart/mixed; boundary=~w\r\n\r\n',
182 [Boundary]),
183 mime_pack(Parts, Out, Boundary).
184pack(Atom, Out) :-
185 atomic(Atom),
186 !,
187 format(Out, '\r\n', []),
188 write(Out, Atom).
189pack(Value, _) :-
190 throw(error(type_error(mime_part, Value), _)).
191
192write_mime_attributes([], _) :- !.
193write_mime_attributes(Atts, Out) :-
194 select(type(Type), Atts, A1),
195 !,
196 ( select(character_set(CharSet), A1, A2)
197 -> format(Out, 'Content-type: ~w; charset=~w\r\n', [Type, CharSet]),
198 write_mime_attributes(A2, Out)
199 ; format(Out, 'Content-type: ~w\r\n', [Type]),
200 write_mime_attributes(A1, Out)
201 ).
202write_mime_attributes([_|T], Out) :-
203 write_mime_attributes(T, Out).
211make_boundary(_, Boundary) :-
212 atomic(Boundary),
213 !.
214make_boundary(_, Boundary) :-
215 get_time(Now),
216 A is random(1<<16),
217 B is random(1<<16),
218 C is random(1<<16),
219 D is random(1<<16),
220 E is random(1<<16),
221 format(atom(Boundary), '------~3f~16r~16r~16r~16r~16r',
222 [Now, A, B, C, D, E])
Create a MIME message
Simple and partial implementation of MIME encoding. MIME is covered by RFC 2045. This library is used by e.g., http_post_data/3 when using the
form_data(+ListOfData)
input specification.MIME decoding is now arranged through
library(mime)
from the clib package, based on the external librfc2045 library. Most likely the functionality of this package will be moved to the same library someday. Packing however is a lot simpler then parsing. */