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