35
36:- module(mime_pack,
37 [ mime_pack/3 38 ]). 39:- autoload(html_write,[print_html/2]). 40:- autoload(mimetype,[file_mime_type/2]). 41:- autoload(library(error),[instantiation_error/1]). 42:- autoload(library(lists),[select/3]).
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 !,
145 format(Out, 'Content-Type: text/html\r\n\r\n', []),
146 print_html(Out, HTML).
147pack(file(File), Out) :-
148 !,
149 ( file_mime_type(File, Type)
150 -> true
151 ; Type = text/plain
152 ),
153 format(Out, 'Content-Type: ~w\r\n\r\n', [Type]),
154 ( Type = text/_
155 -> setup_call_cleanup(
156 open(File, read, In),
157 copy_stream_data(In, Out),
158 close(In))
159 ; stream_property(Out, encoding(OldEncoding)),
160 setup_call_cleanup(
161 set_stream(Out, encoding(octet)),
162 setup_call_cleanup(
163 open(File, read, In, [type(binary)]),
164 copy_stream_data(In, Out),
165 close(In)),
166 set_stream(Out, encoding(OldEncoding)))
167 ).
168pack(stream(In, Len), Out) :-
169 !,
170 format(Out, '\r\n', []),
171 copy_stream_data(In, Out, Len).
172pack(stream(In), Out) :-
173 !,
174 format(Out, '\r\n', []),
175 copy_stream_data(In, Out).
176pack(mime(Atts, Data, []), Out) :- 177 !,
178 write_mime_attributes(Atts, Out),
179 pack(Data, Out).
180pack(mime(_Atts, '', Parts), Out) :-
181 make_boundary(Parts, Boundary),
182 format('Content-type: multipart/mixed; boundary=~w\r\n\r\n',
183 [Boundary]),
184 mime_pack(Parts, Out, Boundary).
185pack(Atom, Out) :-
186 atomic(Atom),
187 !,
188 format(Out, '\r\n', []),
189 write(Out, Atom).
190pack(Value, _) :-
191 throw(error(type_error(mime_part, Value), _)).
192
193write_mime_attributes([], _) :- !.
194write_mime_attributes(Atts, Out) :-
195 select(type(Type), Atts, A1),
196 !,
197 ( select(character_set(CharSet), A1, A2)
198 -> format(Out, 'Content-type: ~w; charset=~w\r\n', [Type, CharSet]),
199 write_mime_attributes(A2, Out)
200 ; format(Out, 'Content-type: ~w\r\n', [Type]),
201 write_mime_attributes(A1, Out)
202 ).
203write_mime_attributes([_|T], Out) :-
204 write_mime_attributes(T, Out).
212make_boundary(_, Boundary) :-
213 atomic(Boundary),
214 !.
215make_boundary(_, Boundary) :-
216 get_time(Now),
217 A is random(1<<16),
218 B is random(1<<16),
219 C is random(1<<16),
220 D is random(1<<16),
221 E is random(1<<16),
222 format(atom(Boundary), '------~3f~16r~16r~16r~16r~16r',
223 [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. */