]> Sergey Matveev's repositories - public-inbox.git/blob - lib/PublicInbox/Eml.pm
No ext_urls
[public-inbox.git] / lib / PublicInbox / Eml.pm
1 # Copyright (C) all contributors <meta@public-inbox.org>
2 # License: AGPL-3.0+ <https://www.gnu.org/licenses/agpl-3.0.txt>
3 #
4 # Lazy MIME parser, it still slurps the full message but keeps short
5 # lifetimes.  Unlike Email::MIME, it doesn't pre-split multipart
6 # messages or do any up-front parsing of headers besides splitting
7 # the header string from the body.
8 #
9 # Contains ideas and code from Email::Simple and Email::MIME
10 # (Perl Artistic License, GPL-1+)
11 #
12 # This aims to replace Email::MIME for our purposes, similar API
13 # but internal field names are differ if they're not 100%-compatible.
14 #
15 # Includes some proposed fixes for Email::MIME:
16 # - header-less sub parts - https://github.com/rjbs/Email-MIME/issues/14
17 # - "0" as boundary - https://github.com/rjbs/Email-MIME/issues/63
18 #
19 # $self = {
20 #       bdy => scalar ref for body (may be undef),
21 #       hdr => scalar ref for header,
22 #       crlf => "\n" or "\r\n" (scalar, not a ref),
23 #
24 #       # filled in during ->each_part
25 #       ct => hash ref returned by parse_content_type
26 # }
27 package PublicInbox::Eml;
28 use strict;
29 use v5.10.1;
30 use Carp qw(croak);
31 use Encode qw(find_encoding); # stdlib
32 use Text::Wrap qw(wrap); # stdlib, we need Perl 5.6+ for $huge
33 use MIME::Base64 3.05; # Perl 5.10.0 / 5.9.2
34 use MIME::QuotedPrint 3.05; # ditto
35
36 my $MIME_Header = find_encoding('MIME-Header');
37
38 use PublicInbox::EmlContentFoo qw(parse_content_type parse_content_disposition);
39 $PublicInbox::EmlContentFoo::STRICT_PARAMS = 0;
40
41 our $mime_parts_limit = 1000; # same as SpamAssassin (not in postfix AFAIK)
42
43 # the rest of the limit names are taken from postfix:
44 our $mime_nesting_limit = 20; # seems enough, Perl sucks, here
45 our $mime_boundary_length_limit = 2048; # same as postfix
46 our $header_size_limit = 102400; # same as postfix
47
48 my %MIME_ENC = (qp => \&enc_qp, base64 => \&encode_base64);
49 my %MIME_DEC = (qp => \&dec_qp, base64 => \&decode_base64);
50 $MIME_ENC{quotedprint} = $MIME_ENC{'quoted-printable'} = $MIME_ENC{qp};
51 $MIME_DEC{quotedprint} = $MIME_DEC{'quoted-printable'} = $MIME_DEC{qp};
52 $MIME_ENC{$_} = \&identity_codec for qw(7bit 8bit binary);
53
54 my %DECODE_ADDRESS = map {
55         ($_ => 1, "Resent-$_" => 1)
56 } qw(From To Cc Sender Reply-To Bcc);
57 my %DECODE_FULL = (
58         Subject => 1,
59         'Content-Description' => 1,
60         'Content-Type' => 1, # not correct, but needed, oh well
61 );
62 our %STR_TYPE = (text => 1);
63 our %STR_SUBTYPE = (plain => 1, html => 1);
64
65 # message/* subtypes we descend into
66 our %MESSAGE_DESCEND = (
67         news => 1, # RFC 1849 (obsolete, but archives are forever)
68         rfc822 => 1, # RFC 2046
69         rfc2822 => 1, # gmime handles this (but not rfc5322)
70         global => 1, # RFC 6532
71 );
72
73 my %re_memo;
74 sub re_memo ($) {
75         my ($k) = @_;
76         # Do not normalize $k with lc/uc; instead strive to keep
77         # capitalization in our codebase consistent.
78         $re_memo{$k} ||= qr/^\Q$k\E:[ \t]*([^\n]*\r?\n # 1st line
79                                         # continuation lines:
80                                         (?:[^:\n]*?[ \t]+[^\n]*\r?\n)*)
81                                         /ismx
82 }
83
84 sub hdr_truncate ($) {
85         my $len = length($_[0]);
86         substr($_[0], $header_size_limit, $len) = '';
87         my $end = rindex($_[0], "\n");
88         if ($end >= 0) {
89                 ++$end;
90                 substr($_[0], $end, $len) = '';
91                 warn "header of $len bytes truncated to $end bytes\n";
92         } else {
93                 $_[0] = '';
94                 warn <<EOF
95 header of $len bytes without `\\n' within $header_size_limit ignored
96 EOF
97         }
98 }
99
100 # compatible with our uses of Email::MIME
101 sub new {
102         my $ref = ref($_[1]) ? $_[1] : \(my $cpy = $_[1]);
103         # substr() can modify the first arg in-place and to avoid
104         # memcpy/memmove on a potentially large scalar.  It does need
105         # to make a copy for $hdr, though.  Idea stolen from Email::Simple.
106
107         # We also prefer index() on common LFLF emails since it's faster
108         # and re scan can bump RSS by length($$ref) on big strings
109         if (index($$ref, "\r\n") < 0 && (my $pos = index($$ref, "\n\n")) >= 0) {
110                 # likely on *nix
111                 my $hdr = substr($$ref, 0, $pos + 2, ''); # sv_chop on $$ref
112                 chop($hdr); # lower SvCUR
113                 hdr_truncate($hdr) if length($hdr) > $header_size_limit;
114                 bless { hdr => \$hdr, crlf => "\n", bdy => $ref }, __PACKAGE__;
115         } elsif ($$ref =~ /\r?\n(\r?\n)/s) {
116                 my $hdr = substr($$ref, 0, $+[0], ''); # sv_chop on $$ref
117                 substr($hdr, -(length($1))) = ''; # lower SvCUR
118                 hdr_truncate($hdr) if length($hdr) > $header_size_limit;
119                 bless { hdr => \$hdr, crlf => $1, bdy => $ref }, __PACKAGE__;
120         } elsif ($$ref =~ /^[a-z0-9-]+[ \t]*:/ims && $$ref =~ /(\r?\n)\z/s) {
121                 # body is optional :P
122                 my $hdr = substr($$ref, 0, $header_size_limit + 1);
123                 hdr_truncate($hdr) if length($hdr) > $header_size_limit;
124                 bless { hdr => \$hdr, crlf => $1 }, __PACKAGE__;
125         } else { # just a body w/o header?
126                 my $hdr = '';
127                 my $eol = ($$ref =~ /(\r?\n)/) ? $1 : "\n";
128                 bless { hdr => \$hdr, crlf => $eol, bdy => $ref }, __PACKAGE__;
129         }
130 }
131
132 sub new_sub {
133         my (undef, $ref) = @_;
134         # special case for messages like <85k5su9k59.fsf_-_@lola.goethe.zz>
135         $$ref =~ /\A(\r?\n)/s or return new(undef, $ref);
136         my $hdr = substr($$ref, 0, $+[0], ''); # sv_chop on $$ref
137         bless { hdr => \$hdr, crlf => $1, bdy => $ref }, __PACKAGE__;
138 }
139
140 # same output as Email::Simple::Header::header_raw, but we extract
141 # headers on-demand instead of parsing them into a list which
142 # requires O(n) lookups anyways
143 sub header_raw {
144         my $re = re_memo($_[1]);
145         my @v = (${ $_[0]->{hdr} } =~ /$re/g);
146         for (@v) {
147                 utf8::decode($_); # SMTPUTF8
148                 # for compatibility w/ Email::Simple::Header,
149                 s/\s+\z//s;
150                 s/\A\s+//s;
151                 s/\r?\n[ \t]*/ /gs;
152         }
153         wantarray ? @v : $v[0];
154 }
155
156 # pick the first Content-Type header to match Email::MIME behavior.
157 # It's usually the right one based on historical archives.
158 sub ct ($) {
159         # PublicInbox::EmlContentFoo::content_type:
160         $_[0]->{ct} //= parse_content_type(header($_[0], 'Content-Type'));
161 }
162
163 # returns a queue of sub-parts iff it's worth descending into
164 sub mp_descend ($$) {
165         my ($self, $nr) = @_; # or $once for top-level
166         my $ct = ct($self);
167         my $type = lc($ct->{type});
168         if ($type eq 'message' && $MESSAGE_DESCEND{lc($ct->{subtype})}) {
169                 my $nxt = new(undef, body_raw($self));
170                 $self->{-call_cb} = $nxt->{is_submsg} = 1;
171                 return [ $nxt ];
172         }
173         return if $type ne 'multipart';
174         my $bnd = $ct->{attributes}->{boundary} // return; # single-part
175         return if $bnd eq '' || length($bnd) >= $mime_boundary_length_limit;
176         $bnd = quotemeta($bnd);
177
178         # this is a multipart message that didn't get descended into in
179         # public-inbox <= 1.5.0, so ensure we call the user callback for
180         # this part to not break PSGI downloads.
181         $self->{-call_cb} = $self->{is_submsg};
182
183         # "multipart" messages can exist w/o a body
184         my $bdy = ($nr ? delete($self->{bdy}) : \(body_raw($self))) or return;
185
186         # Cut at the the first epilogue, not subsequent ones.
187         # *sigh* just the regexp match alone seems to bump RSS by
188         # length($$bdy) on a ~30M string:
189         my $epilogue_missing;
190         if ($$bdy =~ /(?:\r?\n)?^--$bnd--[ \t]*\r?$/sm) {
191                 substr($$bdy, $-[0]) = '';
192         } else {
193                 $epilogue_missing = 1;
194         }
195
196         # *Sigh* split() doesn't work in-place and return CoW strings
197         # because Perl wants to "\0"-terminate strings.  So split()
198         # again bumps RSS by length($$bdy)
199
200         # Quiet warning for "Complex regular subexpression recursion limit"
201         # in case we get many empty parts, it's harmless in this case
202         no warnings 'regexp';
203         my ($pre, @parts) = split(/(?:\r?\n)?(?:^--$bnd[ \t]*\r?\n)+/ms,
204                                 $$bdy,
205                                 # + 3 since we don't want the last part
206                                 # processed to include any other excluded
207                                 # parts ($nr starts at 1, and I suck at math)
208                                 $mime_parts_limit + 3 - $nr);
209
210         if (@parts) { # the usual path if we got this far:
211                 undef $bdy; # release memory ASAP if $nr > 0
212
213                 # compatibility with Email::MIME
214                 $parts[-1] =~ s/\n\r?\n\z/\n/s if $epilogue_missing;
215
216                 # ignore empty parts
217                 @parts = map { new_sub(undef, \$_) } grep /[^ \t\r\n]/s, @parts;
218
219                 # Keep "From: someone..." from preamble in old,
220                 # buggy versions of git-send-email, otherwise drop it
221                 # There's also a case where quoted text showed up in the
222                 # preamble
223                 # <20060515162817.65F0F1BBAE@citi.umich.edu>
224                 unshift(@parts, new_sub(undef, \$pre)) if index($pre, ':') >= 0;
225                 return \@parts;
226         }
227         # "multipart", but no boundary found, treat as single part
228         $self->{bdy} //= $bdy;
229         undef;
230 }
231
232 # $p = [ \@parts, $depth, $idx ]
233 # $idx[0] grows as $depth grows, $idx[1] == $p->[-1] == current part
234 # (callers need to be updated)
235 # \@parts is a queue which empties when we're done with a parent part
236
237 # same usage as PublicInbox::MsgIter::msg_iter
238 # $cb - user-supplied callback sub
239 # $arg - user-supplied arg (think pthread_create)
240 # $once - unref body scalar during iteration
241 # $all - used by IMAP server, only
242 sub each_part {
243         my ($self, $cb, $arg, $once, $all) = @_;
244         my $p = mp_descend($self, $once // 0) or
245                                         return $cb->([$self, 0, 1], $arg);
246
247         $cb->([$self, 0, 0], $arg) if ($all || $self->{-call_cb}); # rare
248
249         $p = [ $p, 0 ];
250         my @s; # our virtual stack
251         my $nr = 0;
252         while ((scalar(@{$p->[0]}) || ($p = pop @s)) &&
253                         ++$nr <= $mime_parts_limit) {
254                 ++$p->[-1]; # bump index
255                 my (undef, @idx) = @$p;
256                 @idx = (join('.', @idx));
257                 my $depth = ($idx[0] =~ tr/././) + 1;
258                 my $sub = shift @{$p->[0]};
259                 if ($depth < $mime_nesting_limit &&
260                                 (my $nxt = mp_descend($sub, $nr))) {
261                         push(@s, $p) if scalar @{$p->[0]};
262                         $p = [ $nxt, @idx, 0 ];
263                         ($all || $sub->{-call_cb}) and
264                                 $cb->([$sub, $depth, @idx], $arg);
265                 } else { # a leaf node
266                         $cb->([$sub, $depth, @idx], $arg);
267                 }
268         }
269 }
270
271 sub enc_qp {
272         # prevent MIME::QuotedPrint from encoding CR as =0D since it's
273         # against RFCs and breaks MUAs
274         $_[0] =~ s/\r\n/\n/sg;
275         encode_qp($_[0], "\r\n");
276 }
277
278 sub dec_qp {
279         # RFC 2822 requires all lines to end in CRLF, though... :<
280         $_[0] = decode_qp($_[0]);
281         $_[0] =~ s/\n/\r\n/sg;
282         $_[0]
283 }
284
285 sub identity_codec { $_[0] }
286
287 ########### compatibility section for existing Email::MIME uses #########
288
289 sub header_obj {
290         bless { hdr => $_[0]->{hdr}, crlf => $_[0]->{crlf} }, __PACKAGE__;
291 }
292
293 sub subparts {
294         my ($self) = @_;
295         my $parts = mp_descend($self, 0) or return ();
296         my $bnd = ct($self)->{attributes}->{boundary} // die 'BUG: no boundary';
297         my $bdy = $self->{bdy};
298         if ($$bdy =~ /\A(.*?)(?:\r?\n)?^--\Q$bnd\E[ \t]*\r?$/sm) {
299                 $self->{preamble} = $1;
300         }
301         if ($$bdy =~ /^--\Q$bnd\E--[ \t]*\r?\n(.+)\z/sm) {
302                 $self->{epilogue} = $1;
303         }
304         @$parts;
305 }
306
307 sub parts_set {
308         my ($self, $parts) = @_;
309
310         # we can't fully support what Email::MIME does,
311         # just what our filter code needs:
312         my $bnd = ct($self)->{attributes}->{boundary} // die <<EOF;
313 ->parts_set not supported for single-part messages
314 EOF
315         my $crlf = $self->{crlf};
316         my $fin_bnd = "$crlf--$bnd--$crlf";
317         $bnd = "$crlf--$bnd$crlf";
318         ${$self->{bdy}} = join($bnd,
319                                 delete($self->{preamble}) // '',
320                                 map { $_->as_string } @$parts
321                                 ) .
322                                 $fin_bnd .
323                                 (delete($self->{epilogue}) // '');
324         undef;
325 }
326
327 sub body_set {
328         my ($self, $body) = @_;
329         my $bdy = $self->{bdy} = ref($body) ? $body : \$body;
330         if (my $cte = header_raw($self, 'Content-Transfer-Encoding')) {
331                 my $enc = $MIME_ENC{lc($cte)} or croak("can't encode `$cte'");
332                 $$bdy = $enc->($$bdy); # in-place
333         }
334         undef;
335 }
336
337 sub body_str_set {
338         my ($self, $str) = @_;
339         my $cs = ct($self)->{attributes}->{charset} //
340                 croak('body_str was given, but no charset is defined');
341         my $enc = find_encoding($cs) // croak "unknown encoding `$cs'";
342         my $tmp;
343         {
344                 my @w;
345                 local $SIG{__WARN__} = sub { push @w, @_ };
346                 $tmp = $enc->encode($str, Encode::FB_WARN);
347                 croak(@w) if @w;
348         };
349         body_set($self, \$tmp);
350 }
351
352 sub content_type { scalar header($_[0], 'Content-Type') }
353
354 # we only support raw header_set
355 sub header_set {
356         my ($self, $pfx, @vals) = @_;
357         my $re = re_memo($pfx);
358         my $hdr = $self->{hdr};
359         return $$hdr =~ s!$re!!g if !@vals;
360         $pfx .= ': ';
361         my $len = 78 - length($pfx);
362         @vals = map {;
363                 utf8::encode(my $v = $_); # to bytes, support SMTPUTF8
364                 # folding differs from Email::Simple::Header,
365                 # we favor tabs for visibility (and space savings :P)
366                 if (length($_) >= $len && (/\n[^ \t]/s || !/\n/s)) {
367                         local $Text::Wrap::columns = $len;
368                         local $Text::Wrap::huge = 'overflow';
369                         $pfx . wrap('', "\t", $v) . $self->{crlf};
370                 } else {
371                         $pfx . $v . $self->{crlf};
372                 }
373         } @vals;
374         $$hdr =~ s!$re!shift(@vals) // ''!ge; # replace current headers, first
375         $$hdr .= join('', @vals); # append any leftovers not replaced
376         # wantarray ? @_[2..$#_] : $_[2]; # Email::Simple::Header compat
377         undef; # we don't care for the return value
378 }
379
380 # note: we only call this method on Subject
381 sub header_str_set {
382         my ($self, $name, @vals) = @_;
383         for (@vals) {
384                 next unless /[^\x20-\x7e]/;
385                 # 39: int((75 - length("Subject: =?UTF-8?B?".'?=') ) / 4) * 3;
386                 s/(.{1,39})/
387                         my $x = $1;
388                         utf8::encode($x); # to octets
389                         '=?UTF-8?B?'.encode_base64($x, '').'?='
390                 /xges;
391         }
392         header_set($self, $name, @vals);
393 }
394
395 sub mhdr_decode ($) {
396         eval { $MIME_Header->decode($_[0], Encode::FB_DEFAULT) } // $_[0];
397 }
398
399 sub filename {
400         my $dis = header_raw($_[0], 'Content-Disposition');
401         my $attrs = parse_content_disposition($dis)->{attributes};
402         my $fn = $attrs->{filename};
403         $fn = ct($_[0])->{attributes}->{name} if !defined($fn) || $fn eq '';
404         (defined($fn) && $fn =~ /=\?/) ? mhdr_decode($fn) : $fn;
405 }
406
407 sub xs_addr_str { # helper for ->header / ->header_str
408         for (@_) { # array from header_raw()
409                 next unless /=\?/;
410                 my @g = parse_email_groups($_); # [ foo => [ E::A::X, ... ]
411                 for (my $i = 0; $i < @g; $i += 2) {
412                         if (defined($g[$i]) && $g[$i] =~ /=\?/) {
413                                 $g[$i] = mhdr_decode($g[$i]);
414                         }
415                         my $addrs = $g[$i + 1];
416                         for my $eax (@$addrs) {
417                                 for my $m (qw(phrase comment)) {
418                                         my $v = $eax->$m;
419                                         $eax->$m(mhdr_decode($v)) if
420                                                         $v && $v =~ /=\?/;
421                                 }
422                         }
423                 }
424                 $_ = format_email_groups(@g);
425         }
426 }
427
428 eval {
429         require Email::Address::XS;
430         Email::Address::XS->import(qw(parse_email_groups format_email_groups));
431         1;
432 } or do {
433         # fallback to just decoding everything, because parsing
434         # email addresses correctly w/o C/XS is slow
435         %DECODE_FULL = (%DECODE_FULL, %DECODE_ADDRESS);
436         %DECODE_ADDRESS = ();
437 };
438
439 *header = \&header_str;
440 sub header_str {
441         my ($self, $name) = @_;
442         my @v = header_raw($self, $name);
443         if ($DECODE_ADDRESS{$name}) {
444                 xs_addr_str(@v);
445         } elsif ($DECODE_FULL{$name}) {
446                 for (@v) {
447                         $_ = mhdr_decode($_) if /=\?/;
448                 }
449         }
450         wantarray ? @v : $v[0];
451 }
452
453 sub body_raw { ${$_[0]->{bdy} // \''}; }
454
455 sub body {
456         my $raw = body_raw($_[0]);
457         my $cte = header_raw($_[0], 'Content-Transfer-Encoding') or return $raw;
458         ($cte) = ($cte =~ /([a-zA-Z0-9\-]+)/) or return $raw; # For S/MIME, etc
459         my $dec = $MIME_DEC{lc($cte)} or return $raw;
460         $dec->($raw);
461 }
462
463 sub body_str {
464         my ($self) = @_;
465         my $ct = ct($self);
466         my $cs = $ct->{attributes}->{charset} // do {
467                 ($STR_TYPE{$ct->{type}} && $STR_SUBTYPE{$ct->{subtype}}) and
468                         return body($self);
469                 croak("can't get body as a string for ",
470                         join("\n\t", header_raw($self, 'Content-Type')));
471         };
472         my $enc = find_encoding($cs) or croak "unknown encoding `$cs'";
473         my $tmp = body($self);
474         # workaround https://rt.cpan.org/Public/Bug/Display.html?id=139622
475         my @w;
476         local $SIG{__WARN__} = sub { push @w, @_ };
477         my $ret = $enc->decode($tmp, Encode::FB_WARN);
478         croak(@w) if @w;
479         $ret;
480 }
481
482 sub as_string {
483         my ($self) = @_;
484         my $ret = ${ $self->{hdr} };
485         return $ret unless defined($self->{bdy});
486         $ret .= $self->{crlf};
487         $ret .= ${$self->{bdy}};
488 }
489
490 # Unlike Email::MIME::charset_set, this only changes the parsed
491 # representation of charset used for search indexing and HTML display.
492 # This does NOT affect what ->as_string returns.
493 sub charset_set {
494         ct($_[0])->{attributes}->{charset} = $_[1];
495 }
496
497 sub crlf { $_[0]->{crlf} // "\n" }
498
499 sub raw_size {
500         my ($self) = @_;
501         my $len = length(${$self->{hdr}});
502         defined($self->{bdy}) and
503                 $len += length(${$self->{bdy}}) + length($self->{crlf});
504         $len;
505 }
506
507 # warnings to ignore when handling spam mailboxes and maybe other places
508 sub warn_ignore {
509         my $s = "@_";
510         # Email::Address::XS warnings
511         $s =~ /^Argument contains empty /
512         || $s =~ /^Element at index [0-9]+.*? contains /
513         # PublicInbox::MsgTime
514         || $s =~ /^bogus TZ offset: .+?, ignoring and assuming \+0000/
515         || $s =~ /^bad Date: .+? in /
516         # Encode::Unicode::UTF7
517         || $s =~ /^Bad UTF7 data escape at /
518 }
519
520 # this expects to be RHS in this assignment: "local $SIG{__WARN__} = ..."
521 sub warn_ignore_cb {
522         my $cb = $SIG{__WARN__} // \&CORE::warn;
523         sub { $cb->(@_) unless warn_ignore(@_) }
524 }
525
526 sub willneed { re_memo($_) for @_ }
527
528 willneed(qw(From To Cc Date Subject Content-Type In-Reply-To References
529                 Message-ID X-Alt-Message-ID));
530
531 1;