xref: /openbsd/gnu/usr.bin/perl/dist/Test/lib/Test.pm (revision 09467b48)
1
2require 5.004;
3package Test;
4
5use strict;
6
7use Carp;
8our ($VERSION, @ISA, @EXPORT, @EXPORT_OK, $ntest, $TestLevel); #public-is
9our ($TESTOUT, $TESTERR, %Program_Lines, $told_about_diff,
10             $ONFAIL, %todo, %history, $planned, @FAILDETAIL); #private-ish
11
12# In case a test is run in a persistent environment.
13sub _reset_globals {
14    %todo       = ();
15    %history    = ();
16    @FAILDETAIL = ();
17    $ntest      = 1;
18    $TestLevel  = 0;		# how many extra stack frames to skip
19    $planned    = 0;
20}
21
22$VERSION = '1.31';
23require Exporter;
24@ISA=('Exporter');
25
26@EXPORT    = qw(&plan &ok &skip);
27@EXPORT_OK = qw($ntest $TESTOUT $TESTERR);
28
29$|=1;
30$TESTOUT = *STDOUT{IO};
31$TESTERR = *STDERR{IO};
32
33# Use of this variable is strongly discouraged.  It is set mainly to
34# help test coverage analyzers know which test is running.
35$ENV{REGRESSION_TEST} = $0;
36
37
38=head1 NAME
39
40Test - provides a simple framework for writing test scripts
41
42=head1 SYNOPSIS
43
44  use strict;
45  use Test;
46
47  # use a BEGIN block so we print our plan before MyModule is loaded
48  BEGIN { plan tests => 14, todo => [3,4] }
49
50  # load your module...
51  use MyModule;
52
53  # Helpful notes.  All note-lines must start with a "#".
54  print "# I'm testing MyModule version $MyModule::VERSION\n";
55
56  ok(0); # failure
57  ok(1); # success
58
59  ok(0); # ok, expected failure (see todo list, above)
60  ok(1); # surprise success!
61
62  ok(0,1);             # failure: '0' ne '1'
63  ok('broke','fixed'); # failure: 'broke' ne 'fixed'
64  ok('fixed','fixed'); # success: 'fixed' eq 'fixed'
65  ok('fixed',qr/x/);   # success: 'fixed' =~ qr/x/
66
67  ok(sub { 1+1 }, 2);  # success: '2' eq '2'
68  ok(sub { 1+1 }, 3);  # failure: '2' ne '3'
69
70  my @list = (0,0);
71  ok @list, 3, "\@list=".join(',',@list);      #extra notes
72  ok 'segmentation fault', '/(?i)success/';    #regex match
73
74  skip(
75    $^O =~ m/MSWin/ ? "Skip if MSWin" : 0,  # whether to skip
76    $foo, $bar  # arguments just like for ok(...)
77  );
78  skip(
79    $^O =~ m/MSWin/ ? 0 : "Skip unless MSWin",  # whether to skip
80    $foo, $bar  # arguments just like for ok(...)
81  );
82
83=head1 DESCRIPTION
84
85This module simplifies the task of writing test files for Perl modules,
86such that their output is in the format that
87L<Test::Harness|Test::Harness> expects to see.
88
89=head1 QUICK START GUIDE
90
91To write a test for your new (and probably not even done) module, create
92a new file called F<t/test.t> (in a new F<t> directory). If you have
93multiple test files, to test the "foo", "bar", and "baz" feature sets,
94then feel free to call your files F<t/foo.t>, F<t/bar.t>, and
95F<t/baz.t>
96
97=head2 Functions
98
99This module defines three public functions, C<plan(...)>, C<ok(...)>,
100and C<skip(...)>.  By default, all three are exported by
101the C<use Test;> statement.
102
103=over 4
104
105=item C<plan(...)>
106
107     BEGIN { plan %theplan; }
108
109This should be the first thing you call in your test script.  It
110declares your testing plan, how many there will be, if any of them
111should be allowed to fail, and so on.
112
113Typical usage is just:
114
115     use Test;
116     BEGIN { plan tests => 23 }
117
118These are the things that you can put in the parameters to plan:
119
120=over
121
122=item C<tests =E<gt> I<number>>
123
124The number of tests in your script.
125This means all ok() and skip() calls.
126
127=item C<todo =E<gt> [I<1,5,14>]>
128
129A reference to a list of tests which are allowed to fail.
130See L</TODO TESTS>.
131
132=item C<onfail =E<gt> sub { ... }>
133
134=item C<onfail =E<gt> \&some_sub>
135
136A subroutine reference to be run at the end of the test script, if
137any of the tests fail.  See L</ONFAIL>.
138
139=back
140
141You must call C<plan(...)> once and only once.  You should call it
142in a C<BEGIN {...}> block, like so:
143
144     BEGIN { plan tests => 23 }
145
146=cut
147
148sub plan {
149    croak "Test::plan(%args): odd number of arguments" if @_ & 1;
150    croak "Test::plan(): should not be called more than once" if $planned;
151
152    local($\, $,);   # guard against -l and other things that screw with
153                     # print
154
155    _reset_globals();
156
157    _read_program( (caller)[1] );
158
159    my $max=0;
160    while (@_) {
161	my ($k,$v) = splice(@_, 0, 2);
162	if ($k =~ /^test(s)?$/) { $max = $v; }
163	elsif ($k eq 'todo' or
164	       $k eq 'failok') { for (@$v) { $todo{$_}=1; }; }
165	elsif ($k eq 'onfail') {
166	    ref $v eq 'CODE' or croak "Test::plan(onfail => $v): must be CODE";
167	    $ONFAIL = $v;
168	}
169	else { carp "Test::plan(): skipping unrecognized directive '$k'" }
170    }
171    my @todo = sort { $a <=> $b } keys %todo;
172    if (@todo) {
173	print $TESTOUT "1..$max todo ".join(' ', @todo).";\n";
174    } else {
175	print $TESTOUT "1..$max\n";
176    }
177    ++$planned;
178    print $TESTOUT "# Running under perl version $] for $^O",
179      (chr(65) eq 'A') ? "\n" : " in a non-ASCII world\n";
180
181    print $TESTOUT "# Win32::BuildNumber ", &Win32::BuildNumber(), "\n"
182      if defined(&Win32::BuildNumber) and defined &Win32::BuildNumber();
183
184    print $TESTOUT "# MacPerl version $MacPerl::Version\n"
185      if defined $MacPerl::Version;
186
187    printf $TESTOUT
188      "# Current time local: %s\n# Current time GMT:   %s\n",
189      scalar(localtime($^T)), scalar(gmtime($^T));
190
191    print $TESTOUT "# Using Test.pm version $VERSION\n";
192
193    # Retval never used:
194    return undef;
195}
196
197sub _read_program {
198  my($file) = shift;
199  return unless defined $file and length $file
200    and -e $file and -f _ and -r _;
201  open(SOURCEFILE, '<', $file) || return;
202  $Program_Lines{$file} = [<SOURCEFILE>];
203  close(SOURCEFILE);
204
205  foreach my $x (@{$Program_Lines{$file}})
206   { $x =~ tr/\cm\cj\n\r//d }
207
208  unshift @{$Program_Lines{$file}}, '';
209  return 1;
210}
211
212=begin _private
213
214=item B<_to_value>
215
216  my $value = _to_value($input);
217
218Converts an C<ok> parameter to its value.  Typically this just means
219running it, if it's a code reference.  You should run all inputted
220values through this.
221
222=cut
223
224sub _to_value {
225    my ($v) = @_;
226    return ref $v eq 'CODE' ? $v->() : $v;
227}
228
229sub _quote {
230    my $str = $_[0];
231    return "<UNDEF>" unless defined $str;
232    $str =~ s/\\/\\\\/g;
233    $str =~ s/"/\\"/g;
234    $str =~ s/\a/\\a/g;
235    $str =~ s/[\b]/\\b/g;
236    $str =~ s/\e/\\e/g;
237    $str =~ s/\f/\\f/g;
238    $str =~ s/\n/\\n/g;
239    $str =~ s/\r/\\r/g;
240    $str =~ s/\t/\\t/g;
241    if (defined $^V && $^V ge v5.6) {
242        $str =~ s/([[:cntrl:]])(?!\d)/sprintf('\\%o',ord($1))/eg;
243        $str =~ s/([[:^print:]])/sprintf('\\x%02X',ord($1))/eg;
244        $str =~ s/([[:^ascii:]])/sprintf('\\x{%X}',ord($1))/eg;
245    }
246    elsif (ord("A") == 65) {
247        $str =~ s/([\0-\037])(?!\d)/sprintf('\\%o',ord($1))/eg;
248        $str =~ s/([\0-\037\177-\377])/sprintf('\\x%02X',ord($1))/eg;
249        $str =~ s/([^\0-\176])/sprintf('\\x{%X}',ord($1))/eg;
250    }
251    else { # Assuming EBCDIC on this ancient Perl
252
253        # The controls except for one are 0-\077, so almost all controls on
254        # EBCDIC platforms will be expressed in octal, instead of just the C0
255        # ones.
256        $str =~ s/([\0-\077])(?!\d)/sprintf('\\%o',ord($1))/eg;
257        $str =~ s/([\0-\077])/sprintf('\\x%02X',ord($1))/eg;
258
259        $str =~ s/([^\0-\xFF])/sprintf('\\x{%X}',ord($1))/eg;
260
261        # What remains to be escaped are the non-ASCII-range characters,
262        # including the one control that isn't in the 0-077 range.
263        # (We don't escape further any ASCII printables.)
264        $str =~ s<[^ !"\$\%#'()*+,\-./0123456789:;\<=\>?\@ABCDEFGHIJKLMNOPQRSTUVWXYZ\[\\\]^_`abcdefghijklmnopqrstuvwxyz{|}~]><sprintf('\\x%02X',ord($1))>eg;
265    }
266    #if( $_[1] ) {
267    #  substr( $str , 218-3 ) = "..."
268    #   if length($str) >= 218 and !$ENV{PERL_TEST_NO_TRUNC};
269    #}
270    return qq("$str");
271}
272
273
274=end _private
275
276=item C<ok(...)>
277
278  ok(1 + 1 == 2);
279  ok($have, $expect);
280  ok($have, $expect, $diagnostics);
281
282This function is the reason for C<Test>'s existence.  It's
283the basic function that
284handles printing "C<ok>" or "C<not ok>", along with the
285current test number.  (That's what C<Test::Harness> wants to see.)
286
287In its most basic usage, C<ok(...)> simply takes a single scalar
288expression.  If its value is true, the test passes; if false,
289the test fails.  Examples:
290
291    # Examples of ok(scalar)
292
293    ok( 1 + 1 == 2 );           # ok if 1 + 1 == 2
294    ok( $foo =~ /bar/ );        # ok if $foo contains 'bar'
295    ok( baz($x + $y) eq 'Armondo' );    # ok if baz($x + $y) returns
296                                        # 'Armondo'
297    ok( @a == @b );             # ok if @a and @b are the same
298                                # length
299
300The expression is evaluated in scalar context.  So the following will
301work:
302
303    ok( @stuff );                       # ok if @stuff has any
304                                        # elements
305    ok( !grep !defined $_, @stuff );    # ok if everything in @stuff
306                                        # is defined.
307
308A special case is if the expression is a subroutine reference (in either
309C<sub {...}> syntax or C<\&foo> syntax).  In
310that case, it is executed and its value (true or false) determines if
311the test passes or fails.  For example,
312
313    ok( sub {   # See whether sleep works at least passably
314      my $start_time = time;
315      sleep 5;
316      time() - $start_time  >= 4
317    });
318
319In its two-argument form, C<ok(I<arg1>, I<arg2>)> compares the two
320scalar values to see if they match.  They match if both are undefined,
321or if I<arg2> is a regex that matches I<arg1>, or if they compare equal
322with C<eq>.
323
324    # Example of ok(scalar, scalar)
325
326    ok( "this", "that" );               # not ok, 'this' ne 'that'
327    ok( "", undef );                    # not ok, "" is defined
328
329The second argument is considered a regex if it is either a regex
330object or a string that looks like a regex.  Regex objects are
331constructed with the qr// operator in recent versions of perl.  A
332string is considered to look like a regex if its first and last
333characters are "/", or if the first character is "m"
334and its second and last characters are both the
335same non-alphanumeric non-whitespace character.  These regexp
336
337Regex examples:
338
339    ok( 'JaffO', '/Jaff/' );    # ok, 'JaffO' =~ /Jaff/
340    ok( 'JaffO', 'm|Jaff|' );   # ok, 'JaffO' =~ m|Jaff|
341    ok( 'JaffO', qr/Jaff/ );    # ok, 'JaffO' =~ qr/Jaff/;
342    ok( 'JaffO', '/(?i)jaff/ ); # ok, 'JaffO' =~ /jaff/i;
343
344If either (or both!) is a subroutine reference, it is run and used
345as the value for comparing.  For example:
346
347    ok sub {
348        open(OUT, '>', 'x.dat') || die $!;
349        print OUT "\x{e000}";
350        close OUT;
351        my $bytecount = -s 'x.dat';
352        unlink 'x.dat' or warn "Can't unlink : $!";
353        return $bytecount;
354      },
355      4
356    ;
357
358The above test passes two values to C<ok(arg1, arg2)> -- the first
359a coderef, and the second is the number 4.  Before C<ok> compares them,
360it calls the coderef, and uses its return value as the real value of
361this parameter. Assuming that C<$bytecount> returns 4, C<ok> ends up
362testing C<4 eq 4>.  Since that's true, this test passes.
363
364Finally, you can append an optional third argument, in
365C<ok(I<arg1>,I<arg2>, I<note>)>, where I<note> is a string value that
366will be printed if the test fails.  This should be some useful
367information about the test, pertaining to why it failed, and/or
368a description of the test.  For example:
369
370    ok( grep($_ eq 'something unique', @stuff), 1,
371        "Something that should be unique isn't!\n".
372        '@stuff = '.join ', ', @stuff
373      );
374
375Unfortunately, a note cannot be used with the single argument
376style of C<ok()>.  That is, if you try C<ok(I<arg1>, I<note>)>, then
377C<Test> will interpret this as C<ok(I<arg1>, I<arg2>)>, and probably
378end up testing C<I<arg1> eq I<arg2>> -- and that's not what you want!
379
380All of the above special cases can occasionally cause some
381problems.  See L</BUGS and CAVEATS>.
382
383=cut
384
385# A past maintainer of this module said:
386# <<ok(...)'s special handling of subroutine references is an unfortunate
387#   "feature" that can't be removed due to compatibility.>>
388#
389
390sub ok ($;$$) {
391    croak "ok: plan before you test!" if !$planned;
392
393    local($\,$,);   # guard against -l and other things that screw with
394                    # print
395
396    my ($pkg,$file,$line) = caller($TestLevel);
397    my $repetition = ++$history{"$file:$line"};
398    my $context = ("$file at line $line".
399		   ($repetition > 1 ? " fail \#$repetition" : ''));
400
401    # Are we comparing two values?
402    my $compare = 0;
403
404    my $ok=0;
405    my $result = _to_value(shift);
406    my ($expected, $isregex, $regex);
407    if (@_ == 0) {
408	$ok = $result;
409    } else {
410        $compare = 1;
411	$expected = _to_value(shift);
412	if (!defined $expected) {
413	    $ok = !defined $result;
414	} elsif (!defined $result) {
415	    $ok = 0;
416	} elsif (ref($expected) eq 'Regexp') {
417	    $ok = $result =~ /$expected/;
418            $regex = $expected;
419	} elsif (($regex) = ($expected =~ m,^ / (.+) / $,sx) or
420	    (undef, $regex) = ($expected =~ m,^ m([^\w\s]) (.+) \1 $,sx)) {
421	    $ok = $result =~ /$regex/;
422	} else {
423	    $ok = $result eq $expected;
424	}
425    }
426    my $todo = $todo{$ntest};
427    if ($todo and $ok) {
428	$context .= ' TODO?!' if $todo;
429	print $TESTOUT "ok $ntest # ($context)\n";
430    } else {
431        # Issuing two seperate prints() causes problems on VMS.
432        if (!$ok) {
433            print $TESTOUT "not ok $ntest\n";
434        }
435	else {
436            print $TESTOUT "ok $ntest\n";
437        }
438
439        $ok or _complain($result, $expected,
440        {
441          'repetition' => $repetition, 'package' => $pkg,
442          'result' => $result, 'todo' => $todo,
443          'file' => $file, 'line' => $line,
444          'context' => $context, 'compare' => $compare,
445          @_ ? ('diagnostic' =>  _to_value(shift)) : (),
446        });
447
448    }
449    ++ $ntest;
450    $ok;
451}
452
453
454sub _complain {
455    my($result, $expected, $detail) = @_;
456    $$detail{expected} = $expected if defined $expected;
457
458    # Get the user's diagnostic, protecting against multi-line
459    # diagnostics.
460    my $diag = $$detail{diagnostic};
461    $diag =~ s/\n/\n#/g if defined $diag;
462
463    my $out = $$detail{todo} ? $TESTOUT : $TESTERR;
464    $$detail{context} .= ' *TODO*' if $$detail{todo};
465    if (!$$detail{compare}) {
466        if (!$diag) {
467            print $out "# Failed test $ntest in $$detail{context}\n";
468        } else {
469            print $out "# Failed test $ntest in $$detail{context}: $diag\n";
470        }
471    } else {
472        my $prefix = "Test $ntest";
473
474        print $out "# $prefix got: " . _quote($result) .
475                       " ($$detail{context})\n";
476        $prefix = ' ' x (length($prefix) - 5);
477        my $expected_quoted = (defined $$detail{regex})
478         ?  'qr{'.($$detail{regex}).'}'  :  _quote($expected);
479
480        print $out "# $prefix Expected: $expected_quoted",
481           $diag ? " ($diag)" : (), "\n";
482
483        _diff_complain( $result, $expected, $detail, $prefix )
484          if defined($expected) and 2 < ($expected =~ tr/\n//);
485    }
486
487    if(defined $Program_Lines{ $$detail{file} }[ $$detail{line} ]) {
488        print $out
489          "#  $$detail{file} line $$detail{line} is: $Program_Lines{ $$detail{file} }[ $$detail{line} ]\n"
490         if $Program_Lines{ $$detail{file} }[ $$detail{line} ]
491          =~ m/[^\s\#\(\)\{\}\[\]\;]/;  # Otherwise it's uninformative
492
493        undef $Program_Lines{ $$detail{file} }[ $$detail{line} ];
494         # So we won't repeat it.
495    }
496
497    push @FAILDETAIL, $detail;
498    return;
499}
500
501
502
503sub _diff_complain {
504    my($result, $expected, $detail, $prefix) = @_;
505    return _diff_complain_external(@_) if $ENV{PERL_TEST_DIFF};
506    return _diff_complain_algdiff(@_)
507      if eval {
508          local @INC = @INC;
509          pop @INC if $INC[-1] eq '.';
510          require Algorithm::Diff; Algorithm::Diff->VERSION(1.15);
511          1;
512      };
513
514    $told_about_diff++ or print $TESTERR <<"EOT";
515# $prefix   (Install the Algorithm::Diff module to have differences in multiline
516# $prefix    output explained.  You might also set the PERL_TEST_DIFF environment
517# $prefix    variable to run a diff program on the output.)
518EOT
519    ;
520    return;
521}
522
523
524
525sub _diff_complain_external {
526    my($result, $expected, $detail, $prefix) = @_;
527    my $diff = $ENV{PERL_TEST_DIFF} || die "WHAAAA?";
528
529    require File::Temp;
530    my($got_fh, $got_filename) = File::Temp::tempfile("test-got-XXXXX");
531    my($exp_fh, $exp_filename) = File::Temp::tempfile("test-exp-XXXXX");
532    unless ($got_fh && $exp_fh) {
533      warn "Can't get tempfiles";
534      return;
535    }
536
537    print $got_fh $result;
538    print $exp_fh $expected;
539    if (close($got_fh) && close($exp_fh)) {
540        my $diff_cmd = "$diff $exp_filename $got_filename";
541        print $TESTERR "#\n# $prefix $diff_cmd\n";
542        if (open(DIFF, '-|', $diff_cmd)) {
543            local $_;
544            while (<DIFF>) {
545                print $TESTERR "# $prefix $_";
546            }
547            close(DIFF);
548        }
549        else {
550            warn "Can't run diff: $!";
551        }
552    } else {
553        warn "Can't write to tempfiles: $!";
554    }
555    unlink($got_filename);
556    unlink($exp_filename);
557    return;
558}
559
560
561
562sub _diff_complain_algdiff {
563    my($result, $expected, $detail, $prefix) = @_;
564
565    my @got = split(/^/, $result);
566    my @exp = split(/^/, $expected);
567
568    my $diff_kind;
569    my @diff_lines;
570
571    my $diff_flush = sub {
572        return unless $diff_kind;
573
574        my $count_lines = @diff_lines;
575        my $s = $count_lines == 1 ? "" : "s";
576        my $first_line = $diff_lines[0][0] + 1;
577
578        print $TESTERR "# $prefix ";
579        if ($diff_kind eq "GOT") {
580            print $TESTERR "Got $count_lines extra line$s at line $first_line:\n";
581            for my $i (@diff_lines) {
582                print $TESTERR "# $prefix  + " . _quote($got[$i->[0]]) . "\n";
583            }
584        } elsif ($diff_kind eq "EXP") {
585            if ($count_lines > 1) {
586                my $last_line = $diff_lines[-1][0] + 1;
587                print $TESTERR "Lines $first_line-$last_line are";
588            }
589            else {
590                print $TESTERR "Line $first_line is";
591            }
592            print $TESTERR " missing:\n";
593            for my $i (@diff_lines) {
594                print $TESTERR "# $prefix  - " . _quote($exp[$i->[1]]) . "\n";
595            }
596        } elsif ($diff_kind eq "CH") {
597            if ($count_lines > 1) {
598                my $last_line = $diff_lines[-1][0] + 1;
599                print $TESTERR "Lines $first_line-$last_line are";
600            }
601            else {
602                print $TESTERR "Line $first_line is";
603            }
604            print $TESTERR " changed:\n";
605            for my $i (@diff_lines) {
606                print $TESTERR "# $prefix  - " . _quote($exp[$i->[1]]) . "\n";
607                print $TESTERR "# $prefix  + " . _quote($got[$i->[0]]) . "\n";
608            }
609        }
610
611        # reset
612        $diff_kind = undef;
613        @diff_lines = ();
614    };
615
616    my $diff_collect = sub {
617        my $kind = shift;
618        &$diff_flush() if $diff_kind && $diff_kind ne $kind;
619        $diff_kind = $kind;
620        push(@diff_lines, [@_]);
621    };
622
623
624    Algorithm::Diff::traverse_balanced(
625        \@got, \@exp,
626        {
627            DISCARD_A => sub { &$diff_collect("GOT", @_) },
628            DISCARD_B => sub { &$diff_collect("EXP", @_) },
629            CHANGE    => sub { &$diff_collect("CH",  @_) },
630            MATCH     => sub { &$diff_flush() },
631        },
632    );
633    &$diff_flush();
634
635    return;
636}
637
638
639
640
641#~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~`~
642
643
644=item C<skip(I<skip_if_true>, I<args...>)>
645
646This is used for tests that under some conditions can be skipped.  It's
647basically equivalent to:
648
649  if( $skip_if_true ) {
650    ok(1);
651  } else {
652    ok( args... );
653  }
654
655...except that the C<ok(1)> emits not just "C<ok I<testnum>>" but
656actually "C<ok I<testnum> # I<skip_if_true_value>>".
657
658The arguments after the I<skip_if_true> are what is fed to C<ok(...)> if
659this test isn't skipped.
660
661Example usage:
662
663  my $if_MSWin =
664    $^O =~ m/MSWin/ ? 'Skip if under MSWin' : '';
665
666  # A test to be skipped if under MSWin (i.e., run except under
667  # MSWin)
668  skip($if_MSWin, thing($foo), thing($bar) );
669
670Or, going the other way:
671
672  my $unless_MSWin =
673    $^O =~ m/MSWin/ ? '' : 'Skip unless under MSWin';
674
675  # A test to be skipped unless under MSWin (i.e., run only under
676  # MSWin)
677  skip($unless_MSWin, thing($foo), thing($bar) );
678
679The tricky thing to remember is that the first parameter is true if
680you want to I<skip> the test, not I<run> it; and it also doubles as a
681note about why it's being skipped. So in the first codeblock above, read
682the code as "skip if MSWin -- (otherwise) test whether C<thing($foo)> is
683C<thing($bar)>" or for the second case, "skip unless MSWin...".
684
685Also, when your I<skip_if_reason> string is true, it really should (for
686backwards compatibility with older Test.pm versions) start with the
687string "Skip", as shown in the above examples.
688
689Note that in the above cases, C<thing($foo)> and C<thing($bar)>
690I<are> evaluated -- but as long as the C<skip_if_true> is true,
691then we C<skip(...)> just tosses out their value (i.e., not
692bothering to treat them like values to C<ok(...)>.  But if
693you need to I<not> eval the arguments when skipping the
694test, use
695this format:
696
697  skip( $unless_MSWin,
698    sub {
699      # This code returns true if the test passes.
700      # (But it doesn't even get called if the test is skipped.)
701      thing($foo) eq thing($bar)
702    }
703  );
704
705or even this, which is basically equivalent:
706
707  skip( $unless_MSWin,
708    sub { thing($foo) }, sub { thing($bar) }
709  );
710
711That is, both are like this:
712
713  if( $unless_MSWin ) {
714    ok(1);  # but it actually appends "# $unless_MSWin"
715            #  so that Test::Harness can tell it's a skip
716  } else {
717    # Not skipping, so actually call and evaluate...
718    ok( sub { thing($foo) }, sub { thing($bar) } );
719  }
720
721=cut
722
723sub skip ($;$$$) {
724    local($\, $,);   # guard against -l and other things that screw with
725                     # print
726
727    my $whyskip = _to_value(shift);
728    if (!@_ or $whyskip) {
729	$whyskip = '' if $whyskip =~ m/^\d+$/;
730        $whyskip =~ s/^[Ss]kip(?:\s+|$)//;  # backwards compatibility, old
731                                            # versions required the reason
732                                            # to start with 'skip'
733        # We print in one shot for VMSy reasons.
734        my $ok = "ok $ntest # skip";
735        $ok .= " $whyskip" if length $whyskip;
736        $ok .= "\n";
737        print $TESTOUT $ok;
738        ++ $ntest;
739        return 1;
740    } else {
741        # backwards compatibility (I think).  skip() used to be
742        # called like ok(), which is weird.  I haven't decided what to do with
743        # this yet.
744#        warn <<WARN if $^W;
745#This looks like a skip() using the very old interface.  Please upgrade to
746#the documented interface as this has been deprecated.
747#WARN
748
749	local($TestLevel) = $TestLevel+1;  #to ignore this stack frame
750        return &ok(@_);
751    }
752}
753
754=back
755
756=cut
757
758END {
759    $ONFAIL->(\@FAILDETAIL) if @FAILDETAIL && $ONFAIL;
760}
761
7621;
763__END__
764
765=head1 TEST TYPES
766
767=over 4
768
769=item * NORMAL TESTS
770
771These tests are expected to succeed.  Usually, most or all of your tests
772are in this category.  If a normal test doesn't succeed, then that
773means that something is I<wrong>.
774
775=item * SKIPPED TESTS
776
777The C<skip(...)> function is for tests that might or might not be
778possible to run, depending
779on the availability of platform-specific features.  The first argument
780should evaluate to true (think "yes, please skip") if the required
781feature is I<not> available.  After the first argument, C<skip(...)> works
782exactly the same way as C<ok(...)> does.
783
784=item * TODO TESTS
785
786TODO tests are designed for maintaining an B<executable TODO list>.
787These tests are I<expected to fail.>  If a TODO test does succeed,
788then the feature in question shouldn't be on the TODO list, now
789should it?
790
791Packages should NOT be released with succeeding TODO tests.  As soon
792as a TODO test starts working, it should be promoted to a normal test,
793and the newly working feature should be documented in the release
794notes or in the change log.
795
796=back
797
798=head1 ONFAIL
799
800  BEGIN { plan test => 4, onfail => sub { warn "CALL 911!" } }
801
802Although test failures should be enough, extra diagnostics can be
803triggered at the end of a test run.  C<onfail> is passed an array ref
804of hash refs that describe each test failure.  Each hash will contain
805at least the following fields: C<package>, C<repetition>, and
806C<result>.  (You shouldn't rely on any other fields being present.)  If the test
807had an expected value or a diagnostic (or "note") string, these will also be
808included.
809
810The I<optional> C<onfail> hook might be used simply to print out the
811version of your package and/or how to report problems.  It might also
812be used to generate extremely sophisticated diagnostics for a
813particularly bizarre test failure.  However it's not a panacea.  Core
814dumps or other unrecoverable errors prevent the C<onfail> hook from
815running.  (It is run inside an C<END> block.)  Besides, C<onfail> is
816probably over-kill in most cases.  (Your test code should be simpler
817than the code it is testing, yes?)
818
819
820=head1 BUGS and CAVEATS
821
822=over
823
824=item *
825
826C<ok(...)>'s special handing of strings which look like they might be
827regexes can also cause unexpected behavior.  An innocent:
828
829    ok( $fileglob, '/path/to/some/*stuff/' );
830
831will fail, since Test.pm considers the second argument to be a regex!
832The best bet is to use the one-argument form:
833
834    ok( $fileglob eq '/path/to/some/*stuff/' );
835
836=item *
837
838C<ok(...)>'s use of string C<eq> can sometimes cause odd problems
839when comparing
840numbers, especially if you're casting a string to a number:
841
842    $foo = "1.0";
843    ok( $foo, 1 );      # not ok, "1.0" ne 1
844
845Your best bet is to use the single argument form:
846
847    ok( $foo == 1 );    # ok "1.0" == 1
848
849=item *
850
851As you may have inferred from the above documentation and examples,
852C<ok>'s prototype is C<($;$$)> (and, incidentally, C<skip>'s is
853C<($;$$$)>). This means, for example, that you can do C<ok @foo, @bar>
854to compare the I<size> of the two arrays. But don't be fooled into
855thinking that C<ok @foo, @bar> means a comparison of the contents of two
856arrays -- you're comparing I<just> the number of elements of each. It's
857so easy to make that mistake in reading C<ok @foo, @bar> that you might
858want to be very explicit about it, and instead write C<ok scalar(@foo),
859scalar(@bar)>.
860
861=item *
862
863This almost definitely doesn't do what you expect:
864
865     ok $thingy->can('some_method');
866
867Why?  Because C<can> returns a coderef to mean "yes it can (and the
868method is this...)", and then C<ok> sees a coderef and thinks you're
869passing a function that you want it to call and consider the truth of
870the result of!  I.e., just like:
871
872     ok $thingy->can('some_method')->();
873
874What you probably want instead is this:
875
876     ok $thingy->can('some_method') && 1;
877
878If the C<can> returns false, then that is passed to C<ok>.  If it
879returns true, then the larger expression S<< C<<
880$thingy->can('some_method') && 1 >> >> returns 1, which C<ok> sees as
881a simple signal of success, as you would expect.
882
883
884=item *
885
886The syntax for C<skip> is about the only way it can be, but it's still
887quite confusing.  Just start with the above examples and you'll
888be okay.
889
890Moreover, users may expect this:
891
892  skip $unless_mswin, foo($bar), baz($quux);
893
894to not evaluate C<foo($bar)> and C<baz($quux)> when the test is being
895skipped.  But in reality, they I<are> evaluated, but C<skip> just won't
896bother comparing them if C<$unless_mswin> is true.
897
898You could do this:
899
900  skip $unless_mswin, sub{foo($bar)}, sub{baz($quux)};
901
902But that's not terribly pretty.  You may find it simpler or clearer in
903the long run to just do things like this:
904
905  if( $^O =~ m/MSWin/ ) {
906    print "# Yay, we're under $^O\n";
907    ok foo($bar), baz($quux);
908    ok thing($whatever), baz($stuff);
909    ok blorp($quux, $whatever);
910    ok foo($barzbarz), thang($quux);
911  } else {
912    print "# Feh, we're under $^O.  Watch me skip some tests...\n";
913    for(1 .. 4) { skip "Skip unless under MSWin" }
914  }
915
916But be quite sure that C<ok> is called exactly as many times in the
917first block as C<skip> is called in the second block.
918
919=back
920
921
922=head1 ENVIRONMENT
923
924If C<PERL_TEST_DIFF> environment variable is set, it will be used as a
925command for comparing unexpected multiline results.  If you have GNU
926diff installed, you might want to set C<PERL_TEST_DIFF> to C<diff -u>.
927If you don't have a suitable program, you might install the
928C<Text::Diff> module and then set C<PERL_TEST_DIFF> to be C<perl
929-MText::Diff -e 'print diff(@ARGV)'>.  If C<PERL_TEST_DIFF> isn't set
930but the C<Algorithm::Diff> module is available, then it will be used
931to show the differences in multiline results.
932
933=for comment
934If C<PERL_TEST_NO_TRUNC> is set, then the initial "Got 'something' but
935expected 'something_else'" readings for long multiline output values aren't
936truncated at about the 230th column, as they normally could be in some
937cases.  Normally you won't need to use this, unless you were carefully
938parsing the output of your test programs.
939
940
941=head1 NOTE
942
943A past developer of this module once said that it was no longer being
944actively developed.  However, rumors of its demise were greatly
945exaggerated.  Feedback and suggestions are quite welcome.
946
947Be aware that the main value of this module is its simplicity.  Note
948that there are already more ambitious modules out there, such as
949L<Test::More> and L<Test::Unit>.
950
951Some earlier versions of this module had docs with some confusing
952typos in the description of C<skip(...)>.
953
954
955=head1 SEE ALSO
956
957L<Test::Harness>
958
959L<Test::Simple>, L<Test::More>, L<Devel::Cover>
960
961L<Test::Builder> for building your own testing library.
962
963L<Test::Unit> is an interesting XUnit-style testing library.
964
965L<Test::Inline> lets you embed tests in code.
966
967
968=head1 AUTHOR
969
970Copyright (c) 1998-2000 Joshua Nathaniel Pritikin.
971
972Copyright (c) 2001-2002 Michael G. Schwern.
973
974Copyright (c) 2002-2004 Sean M. Burke.
975
976Current maintainer: Jesse Vincent. E<lt>jesse@bestpractical.comE<gt>
977
978This package is free software and is provided "as is" without express
979or implied warranty.  It may be used, redistributed and/or modified
980under the same terms as Perl itself.
981
982=cut
983
984# "Your mistake was a hidden intention."
985#  -- /Oblique Strategies/,  Brian Eno and Peter Schmidt
986