user/dev discussion of public-inbox itself
 help / color / mirror / code / Atom feed
From: Eric Wong <e@yhbt.net>
To: meta@public-inbox.org
Subject: [PATCH 05/13] eml: pure-Perl replacement for Email::MIME
Date: Thu,  7 May 2020 21:05:48 +0000	[thread overview]
Message-ID: <20200507210556.22995-6-e@yhbt.net> (raw)
In-Reply-To: <20200507210556.22995-1-e@yhbt.net>

Email::MIME eats memory, wastes time parsing out all the
headers, and some problems can't be fixed without breaking
compatibility for other projects which depend on it.

Informal benchmarks show a ~2x improvement in general
stats gathering scripts and ~10% improvement in HTML
view rendering.

We also don't need the ability to create MIME messages, just
parse them and maybe drop an attachment.

While this isn't the zero-copy or streaming MIME parser of my
dreams; it's still an improvement in that it doesn't keep a
scalar copy of the raw body around along with subparts.  It also
doesn't parse subparts up front, so it can also replace our uses
of Email::Simple.
---
 MANIFEST                      |   2 +
 lib/PublicInbox/Eml.pm        | 393 ++++++++++++++++++++++++++++++++++
 lib/PublicInbox/TestCommon.pm |   9 +-
 t/eml.t                       | 363 +++++++++++++++++++++++++++++++
 4 files changed, 766 insertions(+), 1 deletion(-)
 create mode 100644 lib/PublicInbox/Eml.pm
 create mode 100644 t/eml.t

diff --git a/MANIFEST b/MANIFEST
index 90a05d33..0906448e 100644
--- a/MANIFEST
+++ b/MANIFEST
@@ -105,6 +105,7 @@ lib/PublicInbox/DSKQXS.pm
 lib/PublicInbox/DSPoll.pm
 lib/PublicInbox/Daemon.pm
 lib/PublicInbox/Emergency.pm
+lib/PublicInbox/Eml.pm
 lib/PublicInbox/ExtMsg.pm
 lib/PublicInbox/Feed.pm
 lib/PublicInbox/Filter/Base.pm
@@ -229,6 +230,7 @@ t/ds-leak.t
 t/ds-poll.t
 t/edit.t
 t/emergency.t
+t/eml.t
 t/epoll.t
 t/fail-bin/spamc
 t/feed.t
diff --git a/lib/PublicInbox/Eml.pm b/lib/PublicInbox/Eml.pm
new file mode 100644
index 00000000..0c23bed0
--- /dev/null
+++ b/lib/PublicInbox/Eml.pm
@@ -0,0 +1,393 @@
+# Copyright (C) 2020 all contributors <meta@public-inbox.org>
+# License: AGPL-3.0+ <https://www.gnu.org/licenses/agpl-3.0.txt>
+#
+# Lazy MIME parser, it still slurps the full message but keeps short
+# lifetimes.  Unlike Email::MIME, it doesn't pre-split multipart
+# messages or do any up-front parsing of headers besides splitting
+# the header string from the body.
+#
+# Contains ideas and code from Email::Simple and Email::MIME
+# (Perl Artistic License, GPL-1+)
+#
+# This aims to replace Email::MIME for our purposes, similar API
+# but internal field names are differ if they're not 100%-compatible.
+#
+# Includes some proposed fixes for Email::MIME:
+# - header-less sub parts - https://github.com/rjbs/Email-MIME/issues/14
+# - "0" as boundary - https://github.com/rjbs/Email-MIME/issues/63
+#
+# $self = {
+#	bdy => scalar ref for body (may be undef),
+#	hdr => scalar ref for header,
+#	crlf => "\n" or "\r\n" (scalar, not a ref),
+#
+#	# filled in during ->each_part
+#	ct => hash ref returned by parse_content_type
+# }
+package PublicInbox::Eml;
+use strict;
+use v5.10.1;
+use Carp qw(croak);
+use Encode qw(find_encoding decode encode); # stdlib
+use Text::Wrap qw(wrap); # stdlib, we need Perl 5.6+ for $huge
+
+my $MIME_Header = find_encoding('MIME-Header');
+
+# TODO remove these dependencies
+use Email::MIME::ContentType;
+use Email::MIME::Encodings;
+$Email::MIME::ContentType::STRICT_PARAMS = 0;
+
+our $MAXPARTS = 1000; # same as SpamAssassin
+our $MAXDEPTH = 20; # seems enough, Perl sucks, here
+our $MAXBOUNDLEN = 2048; # same as postfix
+
+my $NO_ENCODE_RE = qr/\A(?:7bit|8bit|binary)[ \t]*(?:;|$)?/i;
+my %DECODE_ADDRESS = map { $_ => 1 } qw(From To Cc Sender Reply-To);
+my %DECODE_FULL = (
+	Subject => 1,
+	'Content-Description' => 1,
+	'Content-Type' => 1, # not correct, but needed, oh well
+);
+our %STR_TYPE = (text => 1);
+our %STR_SUBTYPE = (plain => 1, html => 1);
+
+my %re_memo;
+sub re_memo ($) {
+	my ($k) = @_;
+	# Do not normalize $k with lc/uc; instead strive to keep
+	# capitalization in our codebase consistent.
+	$re_memo{$k} ||= qr/^\Q$k\E:[ \t]*([^\n]*\r?\n # 1st line
+					# continuation lines:
+					(?:[^:\n]*?[ \t]+[^\n]*\r?\n)*)
+					/ismx
+}
+
+# compatible with our uses of Email::MIME
+sub new {
+	my $ref = ref($_[1]) ? $_[1] : \(my $cpy = $_[1]);
+	if ($$ref =~ /(?:\r?\n(\r?\n))/gs) { # likely
+		# This can modify $$ref in-place and to avoid memcpy/memmove
+		# on a potentially large $$ref.  It does need to make a
+		# copy for $hdr, though.  Idea stolen from Email::Simple
+		my $hdr = substr($$ref, 0, pos($$ref), ''); # sv_chop on $$ref
+		substr($hdr, -(length($1))) = ''; # lower SvCUR
+		bless { hdr => \$hdr, crlf => $1, bdy => $ref }, __PACKAGE__;
+	} elsif ($$ref =~ /^[a-z0-9-]+[ \t]*:/ims && $$ref =~ /(\r?\n)\z/s) {
+		# body is optional :P
+		bless { hdr => \($$ref), crlf => $1 }, __PACKAGE__;
+	} else { # nothing useful
+		my $hdr = $$ref = '';
+		bless { hdr => \$hdr, crlf => "\n" }, __PACKAGE__;
+	}
+}
+
+sub new_sub {
+	my (undef, $ref) = @_;
+	# special case for messages like <85k5su9k59.fsf_-_@lola.goethe.zz>
+	$$ref =~ /\A(?:(\r?\n))/gs or goto &new;
+	my $hdr = substr($$ref, 0, pos($$ref), ''); # sv_chop on $$ref
+	bless { hdr => \$hdr, crlf => $1, bdy => $ref }, __PACKAGE__;
+}
+
+# same output as Email::Simple::Header::header_raw, but we extract
+# headers on-demand instead of parsing them into a list which
+# requires O(n) lookups anyways
+sub header_raw {
+	my $re = re_memo($_[1]);
+	my @v = (${ $_[0]->{hdr} } =~ /$re/g);
+	for (@v) {
+		# for compatibility w/ Email::Simple::Header,
+		s/\s+\z//s;
+		s/\A\s+//s;
+		s/\r?\n[ \t]*/ /gs;
+	}
+	wantarray ? @v : $v[0];
+}
+
+# pick the first Content-Type header to match Email::MIME behavior.
+# It's usually the right one based on historical archives.
+sub ct ($) {
+	# Email::MIME::ContentType::content_type:
+	$_[0]->{ct} //= parse_content_type(header($_[0], 'Content-Type'));
+}
+
+sub body_decode ($$) {
+	my $cte = header_raw($_[0], 'Content-Transfer-Encoding');
+	($cte) = ($cte =~ /([a-zA-Z0-9\-]+)/) if $cte; # For S/MIME, etc
+	(!$cte || $cte =~ $NO_ENCODE_RE) ?
+		$_[1] : Email::MIME::Encodings::decode($cte, $_[1], '7bit');
+}
+
+# returns a queue of sub-parts iff it's worth descending into
+# TODO: descend into message/rfc822 parts (Email::MIME didn't)
+sub mp_descend ($$) {
+	my ($self, $nr) = @_; # or $once for top-level
+	my $bnd = ct($self)->{attributes}->{boundary} // return; # single-part
+	return if $bnd eq '' || length($bnd) >= $MAXBOUNDLEN;
+	$bnd = quotemeta($bnd);
+
+	# "multipart" messages can exist w/o a body
+	my $bdy = ($nr ? delete($self->{bdy}) : \(body_raw($self))) or return;
+
+	# Cut at the the first epilogue, not subsequent ones.
+	# *sigh* just the regexp match alone seems to bump RSS by
+	# length($$bdy) on a ~30M string:
+	$$bdy =~ /((?:\r?\n)?^--$bnd--[ \t]*\r?$)/gsm and
+		substr($$bdy, pos($$bdy) - length($1)) = '';
+
+	# *Sigh* split() doesn't work in-place and return CoW strings
+	# because Perl wants to "\0"-terminate strings.  So split()
+	# again bumps RSS by length($$bdy)
+
+	# Quiet warning for "Complex regular subexpression recursion limit"
+	# in case we get many empty parts, it's harmless in this case
+	no warnings 'regexp';
+	my ($pre, @parts) = split(/(?:\r?\n)?(?:^--$bnd[ \t]*\r?\n)+/ms,
+				$$bdy,
+				# + 3 since we don't want the last part
+				# processed to include any other excluded
+				# parts ($nr starts at 1, and I suck at math)
+				$MAXPARTS + 3 - $nr);
+
+	if (@parts) { # the usual path if we got this far:
+		undef $bdy; # release memory ASAP if $nr > 0
+		@parts = grep /[^ \t\r\n]/s, @parts; # ignore empty parts
+
+		# Keep "From: someone..." from preamble in old,
+		# buggy versions of git-send-email, otherwise drop it
+		# There's also a case where quoted text showed up in the
+		# preamble
+		# <20060515162817.65F0F1BBAE@citi.umich.edu>
+		unshift(@parts, $pre) if $pre =~ /:/s;
+		return \@parts;
+	}
+	# "multipart", but no boundary found, treat as single part
+	$self->{bdy} //= $bdy;
+	undef;
+}
+
+# $p = [ \@parts, $depth, $idx ]
+# $idx[0] grows as $depth grows, $idx[1] == $p->[-1] == current part
+# (callers need to be updated)
+# \@parts is a queue which empties when we're done with a parent part
+
+# same usage as PublicInbox::MsgIter::msg_iter
+# $cb - user-supplied callback sub
+# $arg - user-supplied arg (think pthread_create)
+# $once - unref body scalar during iteration
+sub each_part {
+	my ($self, $cb, $arg, $once) = @_;
+	my $p = mp_descend($self, $once // 0) or
+					return $cb->([$self, 0, 0], $arg);
+	$p = [ $p, 0 ];
+	my @s; # our virtual stack
+	my $nr = 0;
+	while ((scalar(@{$p->[0]}) || ($p = pop @s)) && ++$nr <= $MAXPARTS) {
+		++$p->[-1]; # bump index
+		my (undef, @idx) = @$p;
+		@idx = (join('.', @idx));
+		my $depth = ($idx[0] =~ tr/././) + 1;
+		my $sub = new_sub(undef, \(shift @{$p->[0]}));
+		if ($depth < $MAXDEPTH && (my $nxt = mp_descend($sub, $nr))) {
+			push(@s, $p) if scalar @{$p->[0]};
+			$p = [ $nxt, @idx, 0 ];
+		} else { # a leaf node
+			$cb->([$sub, $depth, @idx], $arg);
+		}
+	}
+}
+
+########### compatibility section for existing Email::MIME uses #########
+
+sub header_obj {
+	bless { hdr => $_[0]->{hdr}, crlf => $_[0]->{crlf} }, __PACKAGE__;
+}
+
+sub subparts {
+	my ($self) = @_;
+	my $parts = mp_descend($self, 0) or return ();
+	my $bnd = ct($self)->{attributes}->{boundary} // die 'BUG: no boundary';
+	my $bdy = $self->{bdy};
+	if ($$bdy =~ /\A(.*?)(?:\r?\n)?^--\Q$bnd\E[ \t]*\r?$/sm) {
+		$self->{preamble} = $1;
+	}
+	if ($$bdy =~ /^--\Q$bnd\E--[ \t]*\r?\n(.+)\z/sm) {
+		$self->{epilogue} = $1;
+	}
+	map { new_sub(undef, \$_) } @$parts;
+}
+
+sub parts_set {
+	my ($self, $parts) = @_;
+
+	# we can't fully support what Email::MIME does,
+	# just what our filter code needs:
+	my $bnd = ct($self)->{attributes}->{boundary} // die <<EOF;
+->parts_set not supported for single-part messages
+EOF
+	my $crlf = $self->{crlf};
+	my $fin_bnd = "$crlf--$bnd--$crlf";
+	$bnd = "$crlf--$bnd$crlf";
+	${$self->{bdy}} = join($bnd,
+				delete($self->{preamble}) // '',
+				map { $_->as_string } @$parts
+				) .
+				$fin_bnd .
+				(delete($self->{epilogue}) // '');
+	undef;
+}
+
+sub body_set {
+	my ($self, $body) = @_;
+	my $bdy = $self->{bdy} = ref($body) ? $body : \$body;
+	my $cte = header_raw($self, 'Content-Transfer-Encoding');
+	if ($cte && $cte !~ $NO_ENCODE_RE) {
+		$$bdy = Email::MIME::Encodings::encode($cte, $$bdy)
+	}
+	undef;
+}
+
+sub body_str_set {
+	my ($self, $body_str) = @_;
+	my $charset = ct($self)->{attributes}->{charset} or
+		Carp::confess('body_str was given, but no charset is defined');
+	body_set($self, \(encode($charset, $body_str, Encode::FB_CROAK)));
+}
+
+sub content_type { scalar header($_[0], 'Content-Type') }
+
+# we only support raw header_set
+sub header_set {
+	my ($self, $pfx, @vals) = @_;
+	my $re = re_memo($pfx);
+	my $hdr = $self->{hdr};
+	return $$hdr =~ s!$re!!g if !@vals;
+	$pfx .= ': ';
+	my $len = 78 - length($pfx);
+	@vals = map {;
+		# folding differs from Email::Simple::Header,
+		# we favor tabs for visibility (and space savings :P)
+		if (length($_) >= $len && (/\n[^ \t]/s || !/\n/s)) {
+			local $Text::Wrap::columns = $len;
+			local $Text::Wrap::huge = 'overflow';
+			$pfx . wrap('', "\t", $_) . $self->{crlf};
+		} else {
+			$pfx . $_ . $self->{crlf};
+		}
+	} @vals;
+	$$hdr =~ s!$re!shift(@vals) // ''!ge; # replace current headers, first
+	$$hdr .= join('', @vals); # append any leftovers not replaced
+	# wantarray ? @_[2..$#_] : $_[2]; # Email::Simple::Header compat
+	undef; # we don't care for the return value
+}
+
+# note: we only call this method on Subject
+sub header_str_set {
+	my ($self, $name, @vals) = @_;
+	for (@vals) {
+		next unless /[^\x20-\x7e]/;
+		utf8::encode($_); # to octets
+		# 39: int((75 - length("Subject: =?UTF-8?B?".'?=') ) / 4) * 3;
+		s/(.{1,39})/'=?UTF-8?B?'.encode_base64($1, '').'?='/ges;
+	}
+	header_set($self, $name, @vals);
+}
+
+sub mhdr_decode ($) { eval { $MIME_Header->decode($_[0]) } // $_[0] }
+
+sub filename {
+	my $dis = header_raw($_[0], 'Content-Disposition');
+	my $attrs = parse_content_disposition($dis)->{attributes};
+	my $fn = $attrs->{filename};
+	$fn = ct($_[0])->{attributes}->{name} if !defined($fn) || $fn eq '';
+	(defined($fn) && $fn =~ /=\?/) ? mhdr_decode($fn) : $fn;
+}
+
+sub xs_addr_str { # helper for ->header / ->header_str
+	for (@_) { # array from header_raw()
+		next unless /=\?/;
+		my @g = parse_email_groups($_); # [ foo => [ E::A::X, ... ]
+		for (my $i = 0; $i < @g; $i += 2) {
+			if (defined($g[$i]) && $g[$i] =~ /=\?/) {
+				$g[$i] = mhdr_decode($g[$i]);
+			}
+			my $addrs = $g[$i + 1];
+			for my $eax (@$addrs) {
+				for my $m (qw(phrase comment)) {
+					my $v = $eax->$m;
+					$eax->$m(mhdr_decode($v)) if
+							$v && $v =~ /=\?/;
+				}
+			}
+		}
+		$_ = format_email_groups(@g);
+	}
+}
+
+eval {
+	require Email::Address::XS;
+	Email::Address::XS->import(qw(parse_email_groups format_email_groups));
+	1;
+} or do {
+	# fallback to just decoding everything, because parsing
+	# email addresses correctly w/o C/XS is slow
+	%DECODE_FULL = (%DECODE_FULL, %DECODE_ADDRESS);
+	%DECODE_ADDRESS = ();
+};
+
+*header = \&header_str;
+sub header_str {
+	my ($self, $name) = @_;
+	my @v = header_raw($self, $name);
+	if ($DECODE_ADDRESS{$name}) {
+		xs_addr_str(@v);
+	} elsif ($DECODE_FULL{$name}) {
+		for (@v) {
+			$_ = mhdr_decode($_) if /=\?/;
+		}
+	}
+	wantarray ? @v : $v[0];
+}
+
+sub body_raw { ${$_[0]->{bdy} // \''}; }
+
+sub body { body_decode($_[0], body_raw($_[0])) }
+
+sub body_str {
+	my ($self) = @_;
+	my $ct = ct($self);
+	my $charset = $ct->{attributes}->{charset};
+	if (!$charset) {
+		if ($STR_TYPE{$ct->{type}} && $STR_SUBTYPE{$ct->{subtype}}) {
+			return body($self);
+		}
+		Carp::confess("can't get body as a string for ",
+			join("\n\t", header_raw($self, 'Content-Type')));
+	}
+	decode($charset, body($self), Encode::FB_CROAK);
+}
+
+sub as_string {
+	my ($self) = @_;
+	my $ret = ${ $self->{hdr} };
+	return $ret unless defined($self->{bdy});
+	$ret .= $self->{crlf};
+	$ret .= ${$self->{bdy}};
+}
+
+# Unlike Email::MIME::charset_set, this only changes the parsed
+# representation of charset used for search indexing and HTML display.
+# This does NOT affect what ->as_string returns.
+sub charset_set {
+	ct($_[0])->{attributes}->{charset} = $_[1];
+}
+
+sub crlf { $_[0]->{crlf} // "\n" }
+
+sub willneed { re_memo($_) for @_ }
+
+willneed(qw(From To Cc Date Subject Content-Type In-Reply-To References
+		Message-ID X-Alt-Message-ID));
+
+1;
diff --git a/lib/PublicInbox/TestCommon.pm b/lib/PublicInbox/TestCommon.pm
index cd73b5b6..600843f0 100644
--- a/lib/PublicInbox/TestCommon.pm
+++ b/lib/PublicInbox/TestCommon.pm
@@ -9,7 +9,7 @@ use Fcntl qw(FD_CLOEXEC F_SETFD F_GETFD :seek);
 use POSIX qw(dup2);
 use IO::Socket::INET;
 our @EXPORT = qw(tmpdir tcp_server tcp_connect require_git require_mods
-	run_script start_script key2sub xsys xqx mime_load);
+	run_script start_script key2sub xsys xqx mime_load eml_load);
 
 sub mime_load ($) {
 	my ($path) = @_;
@@ -17,6 +17,13 @@ sub mime_load ($) {
 	PublicInbox::MIME->new(\(do { local $/; <$fh> }));
 }
 
+sub eml_load ($) {
+	my ($path, $cb) = @_;
+	open(my $fh, '<', $path) or die "open $path: $!";
+	binmode $fh;
+	PublicInbox::Eml->new(\(do { local $/; <$fh> }));
+}
+
 sub tmpdir (;$) {
 	my ($base) = @_;
 	require File::Temp;
diff --git a/t/eml.t b/t/eml.t
new file mode 100644
index 00000000..43c735e7
--- /dev/null
+++ b/t/eml.t
@@ -0,0 +1,363 @@
+#!perl -w
+# Copyright (C) 2020 all contributors <meta@public-inbox.org>
+# License: AGPL-3.0+ <https://www.gnu.org/licenses/agpl-3.0.txt>
+use strict;
+use Test::More;
+use PublicInbox::TestCommon;
+use PublicInbox::MsgIter qw(msg_part_text);
+my @classes = qw(PublicInbox::Eml);
+SKIP: {
+	require_mods('Email::MIME', 1);
+	push @classes, 'PublicInbox::MIME';
+};
+use_ok $_ for @classes;
+
+{
+	my $eml = PublicInbox::Eml->new(\(my $str = "a: b\n\nhi\n"));
+	is($str, "hi\n", '->new modified body like Email::Simple');
+	is($eml->body, "hi\n", '->body works');
+	is($eml->as_string, "a: b\n\nhi\n", '->as_string');
+}
+
+for my $cls (@classes) {
+	my $mime = $cls->new(my $orig = "From: x\n\nb");
+	is($mime->as_string, $orig, '->as_string works');
+	is($mime->header_obj->as_string, "From: x\n",
+			'header ->as_string works');
+
+	# headers
+	is($mime->header_raw('From'), 'x', 'header_raw scalar context');
+	$mime = $cls->new("R:\n\tx\nR:\n 1\n");
+	is_deeply([$mime->header_raw('r')], [ 'x', '1' ], 'multi-value');
+	$mime = $cls->new("R:x\nR: 1\n");
+	is_deeply([$mime->header_raw('r')], [ 'x', '1' ], 'multi-value header');
+	$mime = $cls->new("R:x\n R: 1\nR:\n f\n");
+	is_deeply([$mime->header_raw('r')], [ 'x R: 1', 'f' ],
+		'multi-line, multi-value header');
+
+	$mime->header_set('r');
+	is_deeply([$mime->header_raw('r')], [], 'header_set clears');
+	$mime->header_set('r');
+	is_deeply([$mime->header_raw('r')], [], 'header_set clears idempotent');
+	$mime->header_set('r', 'h');
+	is_deeply([$mime->header_raw('r')], ['h'], 'header_set');
+	$mime->header_set('r', 'h', 'i');
+	is_deeply([$mime->header_raw('r')], ['h', 'i'], 'header_set ary');
+	$mime->header_set('rr', 'b');
+	is_deeply([$mime->header_raw('r')], ['h', 'i'],
+				"header_set `rr' did not clobber `r'");
+	is($mime->header_raw('rr'), 'b', 'got set scalar');
+	$mime->header_set('rr', 'b'x100);
+	is($mime->header_raw('rr'), 'b'x100, 'got long set scalar');
+	if ($cls eq 'PublicInbox::Eml') {
+		like($mime->as_string, qr/^rr: b{100}\n(?:\n|\z)/sm,
+			'single token not wrapped');
+	}
+	$mime->header_set('rr', ('b'x100) . ' wrap me');
+	if ($cls eq 'PublicInbox::Eml') {
+		like($mime->as_string, qr/^rr: b{100}\n\twrap me\n/sm,
+			'wrapped after long token');
+	}
+	my $exp = "pre\tformatted\n with\n breaks";
+	$mime->header_set('r', $exp);
+	like($mime->as_string, qr/^r: \Q$exp\E/sm, 'preformatted preserved');
+} # for @classes
+
+for my $cls (@classes) { # make sure we don't add quotes if not needed
+	my $eml = $cls->new("From: John Smith <j\@example.com>\n\n");
+	is($eml->header('From'), 'John Smith <j@example.com>',
+		"name not unnecessarily quoted $cls");
+}
+
+for my $cls (@classes) {
+	my $eml = $cls->new("Subject: foo\n\n");
+	$eml->header_str_set('Subject', "\x{100}");
+	like($eml->header_raw('Subject'), qr/utf-8\?B\?/i,
+		'MIME-B encoded UTF-8 Subject');
+	is_deeply([$eml->header_str('Subject')], [ "\x{100}" ],
+		'got wide character back');
+}
+
+# linux-mips apparently got some messages injected w/o Message-ID
+# and long Subject: lines w/o leading whitespace.
+# What appears in the blobs was generated by V2Writable.
+for my $cls (@classes) {
+	my $eml = $cls->new(<<'EOF');
+Message-ID: <20101130193431@z>
+Subject: something really long
+and really wrong
+From: linux-mips archive injection
+Object-Id: 8c56b7abdd551b1264e6522ededbbed9890cccd0
+EOF
+	is_deeply([ $eml->header('Subject') ],
+		[ 'something really long and really wrong' ],
+		'continued long line w/o leading spaces '.$cls);
+	is_deeply([ $eml->header('From') ],
+		[ 'linux-mips archive injection' ],
+		'subsequent line not corrupted');
+	is_deeply([ $eml->header('Message-ID') ],
+		['<20101130193431@z>'],
+		'preceding line readable');
+} # for @classes
+
+{
+	my $eml = eml_load 't/msg_iter-order.eml';
+	my @parts;
+	my $orig = $eml->as_string;
+	$eml->each_part(sub {
+		my ($part, $level, @ex) = @{$_[0]};
+		my $s = $part->body_str;
+		$s =~ s/\s+//sg;
+		push @parts, [ $s, $level, @ex ];
+	});
+	is_deeply(\@parts, [ [ qw(a 1 1) ], [ qw(b 1 2) ] ], 'order is fine');
+	is($eml->as_string, $orig, 'unchanged by ->each_part');
+	$eml->each_part(sub {}, undef, 1);
+	is(defined($eml) ? $eml->body_raw : '', # old msg_iter clobbers $eml
+		'', 'each_part can clobber body');
+}
+
+# body-less, boundary-less
+for my $cls (@classes) {
+	my $call = 0;
+	$cls->new(<<'EOF')->each_part(sub { $call++ }, 0, 1);
+Content-Type: multipart/mixed; boundary="body-less"
+
+EOF
+	is($call, 1, 'called on bodyless multipart');
+
+	my @tmp;
+	$cls->new(<<'EOF')->each_part(sub { push @tmp, \@_; }, 0, 1);
+Content-Type: multipart/mixed; boundary="boundary-less"
+
+hello world
+EOF
+	is(scalar(@tmp), 1, 'got one part even w/o boundary');
+	is($tmp[0]->[0]->[0]->body, "hello world\n", 'body preserved');
+	is($tmp[0]->[0]->[1], 0, '$depth is zero');
+	is($tmp[0]->[0]->[2], 0, '@idx is zero');
+}
+
+# I guess the following only worked in PI::M because of a happy accident
+# involving inheritance:
+for my $cls (@classes) {
+	my @tmp;
+	my $header_less = <<'EOF';
+Archived-At: <85k5su9k59.fsf_-_@lola.goethe.zz>
+Content-Type: multipart/mixed; boundary="header-less"
+
+--header-less
+
+this is the body
+
+--header-less
+i-haz: header
+
+something else
+
+--header-less--
+EOF
+	my $expect = "this is the body\n";
+	$cls->new($header_less)->each_part(sub { push @tmp, \@_  }, 0, 1);
+	my $body = $tmp[0]->[0]->[0]->body;
+	if ($cls eq 'PublicInbox::Eml') {
+		is($body, $expect, 'body-only subpart in '.$cls);
+	} elsif ($body ne $expect) {
+		diag "W: $cls `$body' != `$expect'";
+	}
+	is($tmp[1]->[0]->[0]->body, "something else\n");
+	is(scalar(@tmp), 2, 'two parts');
+}
+
+if ('one newline before headers') {
+	my $eml = PublicInbox::Eml->new("\nNewline: no Header \n");
+	my @v = $eml->header_raw('Newline');
+	is_deeply(\@v, ['no Header'], 'no header');
+	is($eml->crlf, "\n", 'got CRLF as "\n"');
+	is($eml->body, "");
+}
+
+for my $cls (@classes) { # XXX: matching E::M, but not sure about this
+	my $s = <<EOF;
+Content-Type: multipart/mixed; boundary="b"
+
+--b
+header: only
+--b--
+EOF
+	my $eml = $cls->new(\$s);
+	my $nr = 0;
+	my @v;
+	$eml->each_part(sub {
+		@v = $_[0]->[0]->header_raw('Header');
+		$nr++;
+	});
+	is($nr, 1, 'only one part');
+	is_deeply(\@v, [], "nothing w/o body $cls");
+}
+
+for my $cls (@classes) {
+	my $s = <<EOF; # double epilogue, double the fun
+Content-Type: multipart/mixed; boundary="b"
+
+--b
+should: appear
+
+yes
+
+--b--
+
+--b
+should: not appear
+
+nope
+--b--
+EOF
+	my $eml = $cls->new(\$s);
+	my $nr = 0;
+	$eml->each_part(sub {
+		my $part = $_[0]->[0];
+		is_deeply([$part->header_raw('should')], ['appear'],
+			'only got one header');
+		is($part->body, "yes\n", 'got expected body');
+		$nr++;
+	});
+	is($nr, 1, 'only one part');
+}
+
+for my $cls (@classes) {
+	my $s = <<EOF; # buggy git-send-email versions, again?
+Content-Type: text/plain; =?ISO-8859-1?Q?=20charset=3D=1BOF?=
+Content-Transfer-Encoding: 8bit
+Object-Id: ab0440d8cd6d843bee9a27709a459ce3b2bdb94d (lore/kvm)
+
+\xc4\x80
+EOF
+	my $eml = $cls->new(\$s);
+	my ($str, $err) = msg_part_text($eml, $eml->content_type);
+	is($str, "\x{100}\n", "got wide character by assuming utf-8");
+}
+
+if ('we differ from Email::MIME with final "\n" on missing epilogue') {
+	my $s = <<EOF;
+Content-Type: multipart/mixed; boundary="b"
+
+--b
+header: but
+
+no epilogue
+EOF
+	my $eml = PublicInbox::Eml->new(\$s);
+	is(($eml->subparts)[-1]->body, "no epilogue\n",
+		'final "\n" preserved on missing epilogue');
+}
+
+if ('maxparts is a feature unique to us') {
+	my $eml = eml_load 't/psgi_attach.eml';
+	my @orig;
+	$eml->each_part(sub { push @orig, $_[0]->[0] });
+
+	local $PublicInbox::Eml::MAXPARTS = scalar(@orig);
+	my $i = 0;
+	$eml->each_part(sub {
+		my $cur = $_[0]->[0];
+		my $prv = $orig[$i++];
+		is($cur->body_raw, $prv->body_raw, "part #$i matches");
+	});
+	is($i, scalar(@orig), 'maxparts honored');
+	$PublicInbox::Eml::MAXPARTS--;
+	my @ltd;
+	$eml->each_part(sub { push @ltd, $_[0]->[0] });
+	for ($i = 0; $i <= $#ltd; $i++) {
+		is($ltd[$i]->body_raw, $orig[$i]->body_raw,
+			"part[$i] matches");
+	}
+	is(scalar(@ltd), scalar(@orig) - 1, 'maxparts honored');
+}
+
+SKIP: {
+	require_mods('PublicInbox::MIME', 1);
+	my $eml = eml_load 't/utf8.eml';
+	my $mime = mime_load 't/utf8.eml';
+	for my $h (qw(Subject From To)) {
+		my $v = $eml->header($h);
+		my $m = $mime->header($h);
+		is($v, $m, "decoded -8 $h matches Email::MIME");
+		ok(utf8::is_utf8($v), "$h is UTF-8");
+		ok(utf8::valid($v), "UTF-8 valid $h");
+	}
+	my $s = $eml->body_str;
+	ok(utf8::is_utf8($s), 'body_str is UTF-8');
+	ok(utf8::valid($s), 'UTF-8 valid body_str');
+	my $ref = \(my $x = 'ref');
+	for my $msg ($eml, $mime) {
+		$msg->body_str_set($s .= "\nHI\n");
+		ok(!utf8::is_utf8($msg->body_raw),
+				'raw octets after body_str_set');
+		$s = $msg->body_str;
+		ok(utf8::is_utf8($s), 'body_str is UTF-8 after set');
+		ok(utf8::valid($s), 'UTF-8 valid body_str after set');
+		$msg->body_set($ref);
+		is($msg->body_raw, $$ref, 'body_set worked on scalar ref');
+		$msg->body_set($$ref);
+		is($msg->body_raw, $$ref, 'body_set worked on scalar');
+	}
+	$eml = eml_load 't/iso-2202-jp.eml';
+	$mime = mime_load 't/iso-2202-jp.eml';
+	$s = $eml->body_str;
+	is($s, $mime->body_str, 'ISO-2202-JP body_str');
+	ok(utf8::is_utf8($s), 'ISO-2202-JP => UTF-8 body_str');
+	ok(utf8::valid($s), 'UTF-8 valid body_str');
+
+	$eml = eml_load 't/psgi_attach.eml';
+	$mime = mime_load 't/psgi_attach.eml';
+	is_deeply([ map { $_->body_raw } $eml->subparts ],
+		[ map { $_->body_raw } $mime->subparts ],
+		'raw ->subparts match deeply');
+	is_deeply([ map { $_->body } $eml->subparts ],
+		[ map { $_->body } $mime->subparts ],
+		'->subparts match deeply');
+	for my $msg ($eml, $mime) {
+		my @old = $msg->subparts;
+		$msg->parts_set([]);
+		is_deeply([$msg->subparts], [], 'parts_set can clear');
+		$msg->parts_set([$old[-1]]);
+		is(scalar $msg->subparts, 1, 'only last remains');
+	}
+	is($eml->as_string, $mime->as_string,
+		'as_string matches after parts_set');
+}
+
+for my $cls (@classes) {
+	my $s = <<'EOF';
+Content-Type: text/x-patch; name="=?utf-8?q?vtpm-fakefile.patch?="
+Content-Disposition: attachment; filename="=?utf-8?q?vtpm-makefile.patch?="
+
+EOF
+	is($cls->new($s)->filename, 'vtpm-makefile.patch', 'filename decoded');
+	$s =~ s/^Content-Disposition:.*$//sm;
+	is($cls->new($s)->filename, 'vtpm-fakefile.patch', 'filename fallback');
+	is($cls->new($s)->content_type,
+		'text/x-patch; name="vtpm-fakefile.patch"',
+		'matches Email::MIME output, "correct" or not');
+
+	$s = <<'EOF';
+Content-Type: multipart/foo; boundary=b
+
+--b
+Content-Disposition: attachment; filename="=?utf-8?q?vtpm-makefile.patch?="
+
+a
+--b
+Content-Type: text/x-patch; name="=?utf-8?q?vtpm-fakefile.patch?="
+
+b
+--b--
+EOF
+	my @tmp;
+	$cls->new($s)->each_part(sub { push @tmp, $_[0]->[0]->filename });
+	is_deeply(['vtpm-makefile.patch', 'vtpm-fakefile.patch'], \@tmp,
+		'got filename for both attachments');
+}
+
+done_testing;

  parent reply	other threads:[~2020-05-07 21:05 UTC|newest]

Thread overview: 15+ messages / expand[flat|nested]  mbox.gz  Atom feed  top
2020-05-07 21:05 [PATCH 00/13] eml: pure-Perl replacement for Email::MIME Eric Wong
2020-05-07 21:05 ` [PATCH 01/13] msg_iter: make ->each_part method for PublicInbox::MIME Eric Wong
2020-05-07 21:05 ` [PATCH 02/13] msg_iter: pass $idx as a scalar, not array Eric Wong
2020-05-07 21:05 ` [PATCH 03/13] filter/rubylang: avoid recursing subparts to strip trailers Eric Wong
2020-05-07 21:05 ` [PATCH 04/13] smsg: use capitalization for header retrieval Eric Wong
2020-05-07 21:05 ` Eric Wong [this message]
2020-05-07 21:05 ` [PATCH 06/13] switch read-only Email::Simple users to Eml Eric Wong
2020-05-07 21:05 ` [PATCH 07/13] replace most uses of PublicInbox::MIME with Eml Eric Wong
2020-05-07 21:05 ` [PATCH 08/13] EmlContentFoo: Email::MIME::ContentType replacement Eric Wong
2020-05-07 21:05 ` [PATCH 09/13] EmlContentFoo: relax Encode version requirement Eric Wong
2020-05-07 21:05 ` [PATCH 10/13] eml: remove dependency on Email::MIME::Encodings Eric Wong
2020-05-07 21:05 ` [PATCH 11/13] xt: eml comparison tests Eric Wong
2020-05-08  4:47   ` Eric Wong
2020-05-07 21:05 ` [PATCH 12/13] remove most internal Email::MIME usage Eric Wong
2020-05-07 21:05 ` [PATCH 13/13] eml: drop trailing blank line on missing epilogue Eric Wong

Reply instructions:

You may reply publicly to this message via plain-text email
using any one of the following methods:

* Save the following mbox file, import it into your mail client,
  and reply-to-all from there: mbox

  Avoid top-posting and favor interleaved quoting:
  https://en.wikipedia.org/wiki/Posting_style#Interleaved_style

  List information: http://public-inbox.org/README

* Reply using the --to, --cc, and --in-reply-to
  switches of git-send-email(1):

  git send-email \
    --in-reply-to=20200507210556.22995-6-e@yhbt.net \
    --to=e@yhbt.net \
    --cc=meta@public-inbox.org \
    /path/to/YOUR_REPLY

  https://kernel.org/pub/software/scm/git/docs/git-send-email.html

* If your mail client supports setting the In-Reply-To header
  via mailto: links, try the mailto: link
Be sure your reply has a Subject: header at the top and a blank line before the message body.
Code repositories for project(s) associated with this public inbox

	https://80x24.org/public-inbox.git

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).