xref: /openbsd-src/gnu/usr.bin/perl/ext/B/t/OptreeCheck.pm (revision 50b7afb2c2c0993b0894d4e34bf857cb13ed9c80)
1package OptreeCheck;
2use base 'Exporter';
3use strict;
4use warnings;
5use vars qw($TODO $Level $using_open);
6require "test.pl";
7
8our $VERSION = '0.09';
9
10# now export checkOptree, and those test.pl functions used by tests
11our @EXPORT = qw( checkOptree plan skip skip_all pass is like unlike
12		  require_ok runperl tempfile);
13
14
15# The hints flags will differ if ${^OPEN} is set.
16# The approach taken is to put the hints-with-open in the golden results, and
17# flag that they need to be taken out if ${^OPEN} is set.
18
19if (((caller 0)[10]||{})->{'open<'}) {
20    $using_open = 1;
21}
22
23=head1 NAME
24
25OptreeCheck - check optrees as rendered by B::Concise
26
27=head1 SYNOPSIS
28
29OptreeCheck supports 'golden-sample' regression testing of perl's
30parser, optimizer, bytecode generator, via a single function:
31checkOptree(%in).
32
33It invokes B::Concise upon the sample code, checks that the rendering
34'agrees' with the golden sample, and reports mismatches.
35
36Additionally, the module processes @ARGV (which is typically unused in
37the Core test harness), and thus provides a means to run the tests in
38various modes.
39
40=head1 EXAMPLE
41
42  # your test file
43  use OptreeCheck;
44  plan tests => 1;
45
46  checkOptree (
47    name   => "test-name',	# optional, made from others if not given
48
49    # code-under-test: must provide 1 of them
50    code   => sub {my $a},	# coderef, or source (wrapped and evald)
51    prog   => 'sort @a',	# run in subprocess, aka -MO=Concise
52    bcopts => '-exec',		# $opt or \@opts, passed to BC::compile
53
54    errs   => 'Name "main::a" used only once: possible typo at -e line 1.',
55				# str, regex, [str+] [regex+],
56
57    # various test options
58    # errs   => '.*',		# match against any emitted errs, -w warnings
59    # skip => 1,		# skips test
60    # todo => 'excuse',		# anticipated failures
61    # fail => 1			# force fail (by redirecting result)
62
63    # the 'golden-sample's, (must provide both)
64
65    expect => <<'EOT_EOT', expect_nt => <<'EONT_EONT' );  # start HERE-DOCS
66 # 1  <;> nextstate(main 45 optree.t:23) v
67 # 2  <0> padsv[$a:45,46] M/LVINTRO
68 # 3  <1> leavesub[1 ref] K/REFC,1
69 EOT_EOT
70 # 1  <;> nextstate(main 45 optree.t:23) v
71 # 2  <0> padsv[$a:45,46] M/LVINTRO
72 # 3  <1> leavesub[1 ref] K/REFC,1
73 EONT_EONT
74
75 __END__
76
77=head2 Failure Reports
78
79 Heres a sample failure, as induced by the following command.
80 Note the argument; option=value, after the test-file, more on that later
81
82 $> PERL_CORE=1 ./perl ext/B/t/optree_check.t  testmode=cross
83 ...
84 ok 19 - canonical example w -basic
85 not ok 20 - -exec code: $a=$b+42
86 # Failed at test.pl line 249
87 #      got '1  <;> nextstate(main 600 optree_check.t:208) v
88 # 2  <#> gvsv[*b] s
89 # 3  <$> const[IV 42] s
90 # 4  <2> add[t3] sK/2
91 # 5  <#> gvsv[*a] s
92 # 6  <2> sassign sKS/2
93 # 7  <1> leavesub[1 ref] K/REFC,1
94 # '
95 # expected /(?ms-xi:^1  <;> (?:next|db)state(.*?) v
96 # 2  <\$> gvsv\(\*b\) s
97 # 3  <\$> const\(IV 42\) s
98 # 4  <2> add\[t\d+\] sK/2
99 # 5  <\$> gvsv\(\*a\) s
100 # 6  <2> sassign sKS/2
101 # 7  <1> leavesub\[\d+ refs?\] K/REFC,1
102 # $)/
103 # got:          '2  <#> gvsv[*b] s'
104 # want:  (?^:2  <\$> gvsv\(\*b\) s)
105 # got:          '3  <$> const[IV 42] s'
106 # want:  (?^:3  <\$> const\(IV 42\) s)
107 # got:          '5  <#> gvsv[*a] s'
108 # want:  (?^:5  <\$> gvsv\(\*a\) s)
109 # remainder:
110 # 2  <#> gvsv[*b] s
111 # 3  <$> const[IV 42] s
112 # 5  <#> gvsv[*a] s
113 # these lines not matched:
114 # 2  <#> gvsv[*b] s
115 # 3  <$> const[IV 42] s
116 # 5  <#> gvsv[*a] s
117
118Errors are reported 3 different ways;
119
120The 1st form is directly from test.pl's like() and unlike().  Note
121that this form is used as input, so you can easily cut-paste results
122into test-files you are developing.  Just make sure you recognize
123insane results, to avoid canonizing them as golden samples.
124
125The 2nd and 3rd forms show only the unexpected results and opcodes.
126This is done because it's blindingly tedious to find a single opcode
127causing the failure.  2 different ways are done in case one is
128unhelpful.
129
130=head1 TestCase Overview
131
132checkOptree(%tc) constructs a testcase object from %tc, and then calls
133methods which eventually call test.pl's like() to produce test
134results.
135
136=head2 getRendering
137
138getRendering() runs code or prog or progfile through B::Concise, and
139captures its rendering.  Errors emitted during rendering are checked
140against expected errors, and are reported as diagnostics by default,
141or as failures if 'report=fail' cmdline-option is given.
142
143prog is run in a sub-shell, with $bcopts passed through. This is the way
144to run code intended for main.  The code arg in contrast, is always a
145CODEREF, either because it starts that way as an arg, or because it's
146wrapped and eval'd as $sub = sub {$code};
147
148=head2 mkCheckRex
149
150mkCheckRex() selects the golden-sample for the threaded-ness of the
151platform, and produces a regex which matches the expected rendering,
152and fails when it doesn't match.
153
154The regex includes 'workarounds' which accommodate expected rendering
155variations. These include:
156
157  string constants		# avoid injection
158  line numbers, etc		# args of nexstate()
159  hexadecimal-numbers
160
161  pad-slot-assignments		# for 5.8 compat, and testmode=cross
162  (map|grep)(start|while)	# for 5.8 compat
163
164=head2 mylike
165
166mylike() calls either unlike() or like(), depending on
167expectations.  Mismatch reports are massaged, because the actual
168difference can easily be lost in the forest of opcodes.
169
170=head1 checkOptree API and Operation
171
172Since the arg is a hash, the api is wide-open, and this really is
173about what elements must be or are in the hash, and what they do.  %tc
174is passed to newTestCase(), the ctor, which adds in %proto, a global
175prototype object.
176
177=head2 name => STRING
178
179If name property is not provided, it is synthesized from these params:
180bcopts, note, prog, code.  This is more convenient than trying to do
181it manually.
182
183=head2 code or prog or progfile
184
185Either code or prog or progfile must be present.
186
187=head2 prog => $perl_source_string
188
189prog => $src provides a snippet of code, which is run in a sub-process,
190via test.pl:runperl, and through B::Concise like so:
191
192    './perl -w -MO=Concise,$bcopts_massaged -e $src'
193
194=head2 progfile => $perl_script
195
196progfile => $file provides a file containing a snippet of code which is
197run as per the prog => $src example above.
198
199=head2 code => $perl_source_string || CODEREF
200
201The $code arg is passed to B::Concise::compile(), and run in-process.
202If $code is a string, it's first wrapped and eval'd into a $coderef.
203In either case, $coderef is then passed to B::Concise::compile():
204
205    $subref = eval "sub{$code}";
206    $render = B::Concise::compile($subref)->();
207
208=head2 expect and expect_nt
209
210expect and expect_nt args are the B<golden-sample> renderings, and are
211sampled from known-ok threaded and un-threaded bleadperl (5.9.1) builds.
212They're both required, and the correct one is selected for the platform
213being tested, and saved into the synthesized property B<wanted>.
214
215Individual sample lines may be suffixed with whitespace followed
216by (<|<=|==|>=|>)5.nnnn to select that line only for the listed perl
217version; the whitespace and conditional are stripped.
218
219=head2 bcopts => $bcopts || [ @bcopts ]
220
221When getRendering() runs, it passes bcopts into B::Concise::compile().
222The bcopts arg can be a single string, or an array of strings.
223
224=head2 errs => $err_str_regex || [ @err_str_regexs ]
225
226getRendering() processes the code or prog or progfile arg under warnings,
227and both parsing and optree-traversal errors are collected.  These are
228validated against the one or more errors you specify.
229
230=head1 testcase modifier properties
231
232These properties are set as %tc parameters to change test behavior.
233
234=head2 skip => 'reason'
235
236invokes skip('reason'), causing test to skip.
237
238=head2 todo => 'reason'
239
240invokes todo('reason')
241
242=head2 fail => 1
243
244For code arguments, this option causes getRendering to redirect the
245rendering operation to STDERR, which causes the regex match to fail.
246
247=head2 noanchors => 1
248
249If set, this relaxes the regex check, which is normally pretty strict.
250It's used primarily to validate checkOptree via tests in optree_check.
251
252
253=head1 Synthesized object properties
254
255These properties are added into the test object during execution.
256
257=head2 wanted
258
259This stores the chosen expect expect_nt string.  The OptreeCheck
260object may in the future delete the raw strings once wanted is set,
261thus saving space.
262
263=head2 cross => 1
264
265This tag is added if testmode=cross is passed in as argument.
266It causes test-harness to purposely use the wrong string.
267
268
269=head2 checkErrs
270
271checkErrs() is a getRendering helper that verifies that expected errs
272against those found when rendering the code on the platform.  It is
273run after rendering, and before mkCheckRex.
274
275=cut
276
277use Config;
278use Carp;
279use B::Concise qw(walk_output);
280
281BEGIN {
282    $SIG{__WARN__} = sub {
283	my $err = shift;
284	$err =~ m/Subroutine re::(un)?install redefined/ and return;
285    };
286}
287
288sub import {
289    my $pkg = shift;
290    $pkg->export_to_level(1,'checkOptree', @EXPORT);
291    getCmdLine();	# process @ARGV
292}
293
294
295# %gOpts params comprise a global test-state.  Initial values here are
296# HELP strings, they MUST BE REPLACED by runtime values before use, as
297# is done by getCmdLine(), via import
298
299our %gOpts = 	# values are replaced at runtime !!
300    (
301     # scalar values are help string
302     selftest	=> 'self-tests mkCheckRex vs the reference rendering',
303
304     fail	=> 'force all test to fail, print to stdout',
305     dump	=> 'dump cmdline arg processing',
306     noanchors	=> 'dont anchor match rex',
307
308     # array values are one-of selections, with 1st value as default
309     #  array: 2nd value is used as help-str, 1st val (still) default
310     help	=> [0, 'provides help and exits', 0],
311     testmode	=> [qw/ native cross both /],
312
313     # fixup for VMS, cygwin, which don't have stderr b4 stdout
314     rxnoorder	=> [1, 'if 1, dont req match on -e lines, and -banner',0],
315     strip	=> [1, 'if 1, catch errs and remove from renderings',0],
316     stripv	=> 'if strip&&1, be verbose about it',
317     errs	=> 'expected compile errs, array if several',
318    );
319
320
321# Not sure if this is too much cheating. Officially we say that
322# $Config::Config{usethreads} is true if some sort of threading is in
323# use, in which case we ought to be able to use it in place of the ||
324# below.  However, it is now possible to Configure perl with "threads"
325# but neither ithreads or 5005threads, which forces the re-entrant
326# APIs, but no perl user visible threading.
327
328# This seems to have the side effect that most of perl doesn't think
329# that it's threaded, hence the ops aren't threaded either.  Not sure
330# if this is actually a "supported" configuration, but given that
331# ponie uses it, it's going to be used by something official at least
332# in the interim. So it's nice for tests to all pass.
333
334our $threaded = 1
335  if $Config::Config{useithreads} || $Config::Config{use5005threads};
336our $platform = ($threaded) ? "threaded" : "plain";
337our $thrstat = ($threaded)  ? "threaded" : "nonthreaded";
338
339our %modes = (
340	      both	=> [ 'expect', 'expect_nt'],
341	      native	=> [ ($threaded) ? 'expect' : 'expect_nt'],
342	      cross	=> [ !($threaded) ? 'expect' : 'expect_nt'],
343	      expect	=> [ 'expect' ],
344	      expect_nt	=> [ 'expect_nt' ],
345	      );
346
347our %msgs # announce cross-testing.
348    = (
349       # cross-platform
350       'expect_nt-threaded' => " (nT on T) ",
351       'expect-nonthreaded' => " (T on nT) ",
352       # native - nothing to say (must stay empty - used for $crosstesting)
353       'expect_nt-nonthreaded'	=> '',
354       'expect-threaded'	=> '',
355       );
356
357#######
358sub getCmdLine {	# import assistant
359    # offer help
360    print(qq{\n$0 accepts args to update these state-vars:
361	     turn on a flag by typing its name,
362	     select a value from list by typing name=val.\n    },
363	  mydumper(\%gOpts))
364	if grep /help/, @ARGV;
365
366    # replace values for each key !! MUST MARK UP %gOpts
367    foreach my $opt (keys %gOpts) {
368
369	# scan ARGV for known params
370	if (ref $gOpts{$opt} eq 'ARRAY') {
371
372	    # $opt is a One-Of construct
373	    # replace with valid selection from the list
374
375	    # uhh this WORKS. but it's inscrutable
376	    # grep s/$opt=(\w+)/grep {$_ eq $1} @ARGV and $gOpts{$opt}=$1/e, @ARGV;
377	    my $tval;  # temp
378	    if (grep s/$opt=(\w+)/$tval=$1/e, @ARGV) {
379		# check val before accepting
380		my @allowed = @{$gOpts{$opt}};
381		if (grep { $_ eq $tval } @allowed) {
382		    $gOpts{$opt} = $tval;
383		}
384		else {die "invalid value: '$tval' for $opt\n"}
385	    }
386
387	    # take 1st val as default
388	    $gOpts{$opt} = ${$gOpts{$opt}}[0]
389		if ref $gOpts{$opt} eq 'ARRAY';
390        }
391        else { # handle scalars
392
393	    # if 'opt' is present, true
394	    $gOpts{$opt} = (grep /^$opt/, @ARGV) ? 1 : 0;
395
396	    # override with 'foo' if 'opt=foo' appears
397	    grep s/$opt=(.*)/$gOpts{$opt}=$1/e, @ARGV;
398	}
399     }
400    print("$0 heres current state:\n", mydumper(\%gOpts))
401	if $gOpts{help} or $gOpts{dump};
402
403    exit if $gOpts{help};
404}
405# the above arg-handling cruft should be replaced by a Getopt call
406
407##############################
408# the API (1 function)
409
410sub checkOptree {
411    my $tc = newTestCases(@_);	# ctor
412    my ($rendering);
413
414    print "checkOptree args: ",mydumper($tc) if $tc->{dump};
415    SKIP: {
416	if ($tc->{skip}) {
417	    skip("$tc->{skip} $tc->{name}",
418		    ($gOpts{selftest}
419			? 1
420			: 1 + @{$modes{$gOpts{testmode}}}
421			)
422	    );
423	}
424
425	return runSelftest($tc) if $gOpts{selftest};
426
427	$tc->getRendering();	# get the actual output
428	$tc->checkErrs();
429
430	local $Level = $Level + 2;
431      TODO:
432	foreach my $want (@{$modes{$gOpts{testmode}}}) {
433	    local $TODO = $tc->{todo} if $tc->{todo};
434
435	    $tc->{cross} = $msgs{"$want-$thrstat"};
436
437	    $tc->mkCheckRex($want);
438	    $tc->mylike();
439	}
440    }
441    return;
442}
443
444sub newTestCases {
445    # make test objects (currently 1) from args (passed to checkOptree)
446    my $tc = bless { @_ }, __PACKAGE__
447	or die "test cases are hashes";
448
449    $tc->label();
450
451    # cpy globals into each test
452    foreach my $k (keys %gOpts) {
453	if ($gOpts{$k}) {
454	    $tc->{$k} = $gOpts{$k} unless defined $tc->{$k};
455	}
456    }
457    if ($tc->{errs}) {
458	$tc->{errs} = [$tc->{errs}] unless ref $tc->{errs} eq 'ARRAY';
459    }
460    return $tc;
461}
462
463sub label {
464    # may help get/keep test output consistent
465    my ($tc) = @_;
466    return $tc->{name} if $tc->{name};
467
468    my $buf = (ref $tc->{bcopts})
469	? join(',', @{$tc->{bcopts}}) : $tc->{bcopts};
470
471    foreach (qw( note prog code )) {
472	$buf .= " $_: $tc->{$_}" if $tc->{$_} and not ref $tc->{$_};
473    }
474    return $tc->{name} = $buf;
475}
476
477#################
478# render and its helpers
479
480sub getRendering {
481    my $tc = shift;
482    fail("getRendering: code or prog or progfile is required")
483	unless $tc->{code} or $tc->{prog} or $tc->{progfile};
484
485    my @opts = get_bcopts($tc);
486    my $rendering = ''; # suppress "Use of uninitialized value in open"
487    my @errs;		# collect errs via
488
489
490    if ($tc->{prog}) {
491	$rendering = runperl( switches => ['-w',join(',',"-MO=Concise",@opts)],
492			      prog => $tc->{prog}, stderr => 1,
493			      ); # verbose => 1);
494    } elsif ($tc->{progfile}) {
495	$rendering = runperl( switches => ['-w',join(',',"-MO=Concise",@opts)],
496			      progfile => $tc->{progfile}, stderr => 1,
497			      ); # verbose => 1);
498    } else {
499	my $code = $tc->{code};
500	unless (ref $code eq 'CODE') {
501	    # treat as source, and wrap into subref
502	    #  in caller's package ( to test arg-fixup, comment next line)
503	    my $pkg = '{ package '.caller(1) .';';
504	    {
505		BEGIN { $^H = 0 }
506		no warnings;
507		$code = eval "$pkg sub { $code } }";
508	    }
509	    # return errors
510	    if ($@) { chomp $@; push @errs, $@ }
511	}
512	# set walk-output b4 compiling, which writes 'announce' line
513	walk_output(\$rendering);
514
515	my $opwalker = B::Concise::compile(@opts, $code);
516	die "bad BC::compile retval" unless ref $opwalker eq 'CODE';
517
518      B::Concise::reset_sequence();
519	$opwalker->();
520
521	# kludge error into rendering if its empty.
522	$rendering = $@ if $@ and ! $rendering;
523    }
524    # separate banner, other stuff whose printing order isnt guaranteed
525    if ($tc->{strip}) {
526	$rendering =~ s/(B::Concise::compile.*?\n)//;
527	print "stripped from rendering <$1>\n" if $1 and $tc->{stripv};
528
529	#while ($rendering =~ s/^(.*?(-e) line \d+\.)\n//g) {
530	while ($rendering =~ s/^(.*?(-e|\(eval \d+\).*?) line \d+\.)\n//g) {
531	    print "stripped <$1> $2\n" if $tc->{stripv};
532	    push @errs, $1;
533	}
534	$rendering =~ s/-e syntax OK\n//;
535	$rendering =~ s/-e had compilation errors\.\n//;
536    }
537    $tc->{got}	   = $rendering;
538    $tc->{goterrs} = \@errs if @errs;
539    return $rendering, @errs;
540}
541
542sub get_bcopts {
543    # collect concise passthru-options if any
544    my ($tc) = shift;
545    my @opts = ();
546    if ($tc->{bcopts}) {
547	@opts = (ref $tc->{bcopts} eq 'ARRAY')
548	    ? @{$tc->{bcopts}} : ($tc->{bcopts});
549    }
550    return @opts;
551}
552
553sub checkErrs {
554    # check rendering errs against expected errors, reduce and report
555    my $tc = shift;
556
557    # check for agreement (order not important)
558    my (%goterrs, @missed);
559    @goterrs{@{$tc->{goterrs}}} = (1) x scalar @{$tc->{goterrs}}
560	if $tc->{goterrs};
561
562    foreach my $want (@{$tc->{errs}}) {
563	if (ref $want) {
564	    my $seen;
565	    foreach my $k (keys %goterrs) {
566		next unless $k =~ $want;
567		delete $goterrs{$k};
568		++$seen;
569	    }
570	    push @missed, $want unless $seen;
571	} else {
572	    push @missed, $want unless defined delete $goterrs{$want};
573	}
574    }
575
576    @missed = sort @missed;
577    my @got = sort keys %goterrs;
578
579    if (@{$tc->{errs}}) {
580	is(@missed + @got, 0, "Only got expected errors for $tc->{name}")
581    } else {
582	# @missed must be 0 here.
583	is(scalar @got, 0, "Got no errors for $tc->{name}")
584    }
585    _diag(join "\n", "got unexpected:", @got) if @got;
586    _diag(join "\n", "missed expected:", @missed) if @missed;
587}
588
589=head1 mkCheckRex ($tc)
590
591It selects the correct golden-sample from the test-case object, and
592converts it into a Regexp which should match against the original
593golden-sample (used in selftest, see below), and on the renderings
594obtained by applying the code on the perl being tested.
595
596The selection is driven by platform mostly, but also by test-mode,
597which rather complicates the code.  This is worsened by the potential
598need to make platform specific conversions on the reftext.
599
600but is otherwise as strict as possible.  For example, it should *not*
601match when opcode flags change, or when optimizations convert an op to
602an ex-op.
603
604
605=head2 match criteria
606
607The selected golden-sample is massaged to eliminate various match
608irrelevancies.  This is done so that the tests don't fail just because
609you added a line to the top of the test file.  (Recall that the
610renderings contain the program's line numbers).  Similar cleanups are
611done on "strings", hex-constants, etc.
612
613The need to massage is reflected in the 2 golden-sample approach of
614the test-cases; we want the match to be as rigorous as possible, and
615thats easier to achieve when matching against 1 input than 2.
616
617Opcode arguments (text within braces) are disregarded for matching
618purposes.  This loses some info in 'add[t5]', but greatly simplifies
619matching 'nextstate(main 22 (eval 10):1)'.  Besides, we are testing
620for regressions, not for complete accuracy.
621
622The regex is anchored by default, but can be suppressed with
623'noanchors', allowing 1-liner tests to succeed if opcode is found.
624
625=cut
626
627# needless complexity due to 'too much info' from B::Concise v.60
628my $announce = 'B::Concise::compile\(CODE\(0x[0-9a-f]+\)\)';;
629
630sub mkCheckRex {
631    # converts expected text into Regexp which should match against
632    # unaltered version.  also adjusts threaded => non-threaded
633    my ($tc, $want) = @_;
634
635    my $str = $tc->{expect} || $tc->{expect_nt};	# standard bias
636    $str = $tc->{$want} if $want && $tc->{$want};	# stated pref
637
638    die("no '$want' golden-sample found: $tc->{name}") unless $str;
639
640    $str =~ s/^\# //mg;	# ease cut-paste testcase authoring
641
642    # strip out conditional lines
643
644    $str =~ s{^(.*?)\s+(<|<=|==|>=|>)\s*(5\.\d+)\ *\n}
645     {
646	my ($line, $cmp, $version) = ($1,$2,$3);
647	my $repl = "";
648	if (  $cmp eq '<'  ? $] <  $version
649	    : $cmp eq '<=' ? $] <= $version
650	    : $cmp eq '==' ? $] == $version
651	    : $cmp eq '>=' ? $] >= $version
652	    : $cmp eq '>'  ? $] >  $version
653	    : die("bad comparision '$cmp' in string [$str]\n")
654	) {
655	    $repl = "$line\n";
656	}
657	$repl;
658     }gem;
659
660    $tc->{wantstr} = $str;
661
662    # make targ args wild
663    $str =~ s/\[t\d+\]/[t\\d+]/msg;
664
665    # escape bracing, etc.. manual \Q (doesn't escape '+')
666    $str =~ s/([\[\]()*.\$\@\#\|{}])/\\$1/msg;
667    # $str =~ s/(?<!\\)([\[\]\(\)*.\$\@\#\|{}])/\\$1/msg;
668
669    # treat dbstate like nextstate (no in-debugger false reports)
670    # Note also that there may be 1 level of () nexting, if there's an eval
671    # Seems easiest to explicitly match the eval, rather than trying to parse
672    # for full balancing and then substitute .*?
673    # In which case, we can continue to match for the eval in the rexexp built
674    # from the golden result.
675
676    $str =~ s!(?:next|db)state
677	      \\\(			# opening literal ( (backslash escaped)
678	      [^()]*?			# not ()
679	      (\\\(eval\ \d+\\\)	# maybe /eval \d+/ in ()
680	       [^()]*?			# which might be followed by something
681	      )?
682	      \\\)			# closing literal )
683	     !'(?:next|db)state\\([^()]*?' .
684	      ($1 && '\\(eval \\d+\\)[^()]*')	# Match the eval if present
685	      . '\\)'!msgxe;
686    # widened for -terse mode
687    $str =~ s/(?:next|db)state/(?:next|db)state/msg;
688    if (!$using_open && $tc->{strip_open_hints}) {
689      $str =~ s[(			# capture
690		 \(\?:next\|db\)state	# the regexp matching next/db state
691		 .*			# all sorts of things follow it
692		 v			# The opening v
693		)
694		(?:(:>,<,%,\\{)		# hints when open.pm is in force
695		   |(:>,<,%))		# (two variations)
696		(\ ->(?:-|[0-9a-z]+))?
697		$
698	       ]
699	[$1 . ($2 && ':{') . $4]xegm;	# change to the hints without open.pm
700    }
701
702
703    # don't care about:
704    $str =~ s/:-?\d+,-?\d+/:-?\\d+,-?\\d+/msg;		# FAKE line numbers
705    $str =~ s/match\\\(.*?\\\)/match\(.*?\)/msg;	# match args
706    $str =~ s/(0x[0-9A-Fa-f]+)/0x[0-9A-Fa-f]+/msg;	# hexnum values
707    $str =~ s/".*?"/".*?"/msg;				# quoted strings
708    $str =~ s/FAKE:(\w):\d+/FAKE:$1:\\d+/msg;		# parent pad index
709
710    $str =~ s/(\d refs?)/\\d+ refs?/msg;		# 1 ref, 2+ refs (plural)
711    $str =~ s/leavesub \[\d\]/leavesub [\\d]/msg;	# for -terse
712    #$str =~ s/(\s*)\n/\n/msg;				# trailing spaces
713
714    croak "whitespace only reftext found for '$want': $tc->{name}"
715	unless $str =~ /\w+/; # fail unless a real test
716
717    # $str = '.*'	if 1;	# sanity test
718    # $str .= 'FAIL'	if 1;	# sanity test
719
720    # allow -eval, banner at beginning of anchored matches
721    $str = "(-e .*?)?(B::Concise::compile.*?)?\n" . $str
722	unless $tc->{noanchors} or $tc->{rxnoorder};
723
724    my $qr = ($tc->{noanchors})	? qr/$str/ms : qr/^$str$/ms ;
725
726    $tc->{rex}		= $qr;
727    $tc->{rexstr}	= $str;
728    $tc;
729}
730
731##############
732# compare and report
733
734sub mylike {
735    # reworked mylike to use hash-obj
736    my $tc	= shift;
737    my $got	= $tc->{got};
738    my $want	= $tc->{rex};
739    my $cmnt	= $tc->{name};
740    my $cross	= $tc->{cross};
741
742    # bad is anticipated failure
743    my $bad = ($cross && $tc->{crossfail}) || (!$cross && $tc->{fail});
744
745    my $ok = $bad ? unlike ($got, $want, $cmnt) : like ($got, $want, $cmnt);
746
747    reduceDiffs ($tc) if not $ok;
748
749    return $ok;
750}
751
752sub reduceDiffs {
753    # isolate the real diffs and report them.
754    # i.e. these kinds of errs:
755    # 1. missing or extra ops.  this skews all following op-sequences
756    # 2. single op diff, the rest of the chain is unaltered
757    # in either case, std err report is inadequate;
758
759    my $tc	= shift;
760    my $got	= $tc->{got};
761    my @got	= split(/\n/, $got);
762    my $want	= $tc->{wantstr};
763    my @want	= split(/\n/, $want);
764
765    # split rexstr into units that should eat leading lines.
766    my @rexs = map qr/$_/, split (/\n/, $tc->{rexstr});
767
768    foreach my $rex (@rexs) {
769        my $exp = shift @want;
770        my $line = shift @got;
771        # remove matches, and report
772        unless ($got =~ s/($rex\n)//msg) {
773            _diag("got:\t\t'$line'\nwant:\t $rex\n");
774        }
775    }
776    _diag("remainder:\n$got");
777    _diag("these lines not matched:\n$got\n");
778}
779
780=head1 Global modes
781
782Unusually, this module also processes @ARGV for command-line arguments
783which set global modes.  These 'options' change the way the tests run,
784essentially reusing the tests for different purposes.
785
786
787
788Additionally, there's an experimental control-arg interface (i.e.
789subject to change) which allows the user to set global modes.
790
791
792=head1 Testing Method
793
794At 1st, optreeCheck used one reference-text, but the differences
795between Threaded and Non-threaded renderings meant that a single
796reference (sampled from say, threaded) would be tricky and iterative
797to convert for testing on a non-threaded build.  Worse, this conflicts
798with making tests both strict and precise.
799
800We now use 2 reference texts, the right one is used based upon the
801build's threaded-ness.  This has several benefits:
802
803 1. native reference data allows closer/easier matching by regex.
804 2. samples can be eyeballed to grok T-nT differences.
805 3. data can help to validate mkCheckRex() operation.
806 4. can develop regexes which accommodate T-nT differences.
807 5. can test with both native and cross-converted regexes.
808
809Cross-testing (expect_nt on threaded, expect on non-threaded) exposes
810differences in B::Concise output, so mkCheckRex has code to do some
811cross-test manipulations.  This area needs more work.
812
813=head1 Test Modes
814
815One consequence of a single-function API is difficulty controlling
816test-mode.  I've chosen for now to use a package hash, %gOpts, to store
817test-state.  These properties alter checkOptree() function, either
818short-circuiting to selftest, or running a loop that runs the testcase
8192^N times, varying conditions each time.  (current N is 2 only).
820
821So Test-mode is controlled with cmdline args, also called options below.
822Run with 'help' to see the test-state, and how to change it.
823
824=head2  selftest
825
826This argument invokes runSelftest(), which tests a regex against the
827reference renderings that they're made from.  Failure of a regex match
828its 'mold' is a strong indicator that mkCheckRex is buggy.
829
830That said, selftest mode currently runs a cross-test too, they're not
831completely orthogonal yet.  See below.
832
833=head2 testmode=cross
834
835Cross-testing is purposely creating a T-NT mismatch, looking at the
836fallout, which helps to understand the T-NT differences.
837
838The tweaking appears contrary to the 2-refs philosophy, but the tweaks
839will be made in conversion-specific code, which (will) handles T->NT
840and NT->T separately.  The tweaking is incomplete.
841
842A reasonable 1st step is to add tags to indicate when TonNT or NTonT
843is known to fail.  This needs an option to force failure, so the
844test.pl reporting mechanics show results to aid the user.
845
846=head2 testmode=native
847
848This is normal mode.  Other valid values are: native, cross, both.
849
850=head2 checkOptree Notes
851
852Accepts test code, renders its optree using B::Concise, and matches
853that rendering against a regex built from one of 2 reference
854renderings %tc data.
855
856The regex is built by mkCheckRex(\%tc), which scrubs %tc data to
857remove match-irrelevancies, such as (args) and [args].  For example,
858it strips leading '# ', making it easy to cut-paste new tests into
859your test-file, run it, and cut-paste actual results into place.  You
860then retest and reedit until all 'errors' are gone.  (now make sure you
861haven't 'enshrined' a bug).
862
863name: The test name.  May be augmented by a label, which is built from
864important params, and which helps keep names in sync with whats being
865tested.
866
867=cut
868
869sub runSelftest {
870    # tests the regex produced by mkCheckRex()
871    # by using on the expect* text it was created with
872    # failures indicate a code bug,
873    # OR regexs plugged into the expect* text (which defeat conversions)
874    my $tc = shift;
875
876    for my $provenance (qw/ expect expect_nt /) {
877	#next unless $tc->{$provenance};
878
879	$tc->mkCheckRex($provenance);
880	$tc->{got} = $tc->{wantstr};	# fake the rendering
881	$tc->mylike();
882    }
883}
884
885my $dumploaded = 0;
886
887sub mydumper {
888
889    do { Dumper(@_); return } if $dumploaded;
890
891    eval "require Data::Dumper"
892	or do{
893	    print "Sorry, Data::Dumper is not available\n";
894	    print "half hearted attempt:\n";
895	    foreach my $it (@_) {
896		if (ref $it eq 'HASH') {
897		    print " $_ => $it->{$_}\n" foreach sort keys %$it;
898		}
899	    }
900	    return;
901	};
902
903    Data::Dumper->import;
904    $Data::Dumper::Sortkeys = 1;
905    $dumploaded++;
906    Dumper(@_);
907}
908
909############################
910# support for test writing
911
912sub preamble {
913    my $testct = shift || 1;
914    return <<EO_HEADER;
915#!perl
916
917BEGIN {
918    chdir q(t);
919    \@INC = qw(../lib ../ext/B/t);
920    require q(./test.pl);
921}
922use OptreeCheck;
923plan tests => $testct;
924
925EO_HEADER
926
927}
928
929sub OptreeCheck::wrap {
930    my $code = shift;
931    $code =~ s/(?:(\#.*?)\n)//gsm;
932    $code =~ s/\s+/ /mgs;
933    chomp $code;
934    return unless $code =~ /\S/;
935    my $comment = $1;
936
937    my $testcode = qq{
938
939checkOptree(note   => q{$comment},
940	    bcopts => q{-exec},
941	    code   => q{$code},
942	    expect => <<EOT_EOT, expect_nt => <<EONT_EONT);
943ThreadedRef
944    paste your 'golden-example' here, then retest
945EOT_EOT
946NonThreadedRef
947    paste your 'golden-example' here, then retest
948EONT_EONT
949
950};
951    return $testcode;
952}
953
954sub OptreeCheck::gentest {
955    my ($code,$opts) = @_;
956    my $rendering = getRendering({code => $code});
957    my $testcode = OptreeCheck::wrap($code);
958    return unless $testcode;
959
960    # run the prog, capture 'reference' concise output
961    my $preamble = preamble(1);
962    my $got = runperl( prog => "$preamble $testcode", stderr => 1,
963		       #switches => ["-I../ext/B/t", "-MOptreeCheck"],
964		       );  #verbose => 1);
965
966    # extract the 'reftext' ie the got 'block'
967    if ($got =~ m/got \'.*?\n(.*)\n\# \'\n\# expected/s) {
968	my $goldentxt = $1;
969	#and plug it into the test-src
970	if ($threaded) {
971	    $testcode =~ s/ThreadedRef/$goldentxt/;
972	} else {
973	    $testcode =~ s/NonThreadRef/$goldentxt/;
974	}
975	my $b4 = q{expect => <<EOT_EOT, expect_nt => <<EONT_EONT};
976	my $af = q{expect => <<'EOT_EOT', expect_nt => <<'EONT_EONT'};
977	$testcode =~ s/$b4/$af/;
978
979	return $testcode;
980    }
981    return '';
982}
983
984
985sub OptreeCheck::processExamples {
986    my @files = @_;
987
988    # gets array of paragraphs, which should be code-samples.  They're
989    # turned into optreeCheck tests,
990
991    foreach my $file (@files) {
992	open (my $fh, $file) or die "cant open $file: $!\n";
993	$/ = "";
994	my @chunks = <$fh>;
995	print preamble (scalar @chunks);
996	foreach my $t (@chunks) {
997	    print "\n\n=for gentest\n\n# chunk: $t=cut\n\n";
998	    print OptreeCheck::gentest ($t);
999	}
1000    }
1001}
1002
1003# OK - now for the final insult to your good taste...
1004
1005if ($0 =~ /OptreeCheck\.pm/) {
1006
1007    #use lib 't';
1008    require './t/test.pl';
1009
1010    # invoked as program.  Work like former gentest.pl,
1011    # ie read files given as cmdline args,
1012    # convert them to usable test files.
1013
1014    require Getopt::Std;
1015    Getopt::Std::getopts('') or
1016	die qq{ $0 sample-files*    # no options
1017
1018	  expecting filenames as args.  Each should have paragraphs,
1019	  these are converted to checkOptree() tests, and printed to
1020	  stdout.  Redirect to file then edit for test. \n};
1021
1022  OptreeCheck::processExamples(@ARGV);
1023}
1024
10251;
1026
1027__END__
1028
1029=head1 TEST DEVELOPMENT SUPPORT
1030
1031This optree regression testing framework needs tests in order to find
1032bugs.  To that end, OptreeCheck has support for developing new tests,
1033according to the following model:
1034
1035 1. write a set of sample code into a single file, one per
1036    paragraph.  Add <=for gentest> blocks if you care to, or just look at
1037    f_map and f_sort in ext/B/t/ for examples.
1038
1039 2. run OptreeCheck as a program on the file
1040
1041   ./perl -Ilib ext/B/t/OptreeCheck.pm -w ext/B/t/f_map
1042   ./perl -Ilib ext/B/t/OptreeCheck.pm -w ext/B/t/f_sort
1043
1044   gentest reads the sample code, runs each to generate a reference
1045   rendering, folds this rendering into an optreeCheck() statement,
1046   and prints it to stdout.
1047
1048 3. run the output file as above, redirect to files, then rerun on
1049    same build (for sanity check), and on thread-opposite build.  With
1050    editor in 1 window, and cmd in other, it's fairly easy to cut-paste
1051    the gots into the expects, easier than running step 2 on both
1052    builds then trying to sdiff them together.
1053
1054=head1 CAVEATS
1055
1056This code is purely for testing core. While checkOptree feels flexible
1057enough to be stable, the whole selftest framework is subject to change
1058w/o notice.
1059
1060=cut
1061