print "1..53\n";
# First test whether the number stringification works okay.
-# (Testing with == would exercize the IV/NV part, not the PV.)
+# (Testing with == would exercise the IV/NV part, not the PV.)
$a = 1; "$a";
print $a eq "1" ? "ok 1\n" : "not ok 1 # $a\n";
#!./perl
-# check to see if subroutine declarations work everwhere
+# check to see if subroutine declarations work everywhere
sub one {
print "ok 1\n";
"normal inplace edit");
}
- # test * equivalency RT #70802
+ # test * equivalence RT #70802
{
for my $file (@ifiles) {
runperl( prog => 'print qq(bar\n);',
OPTIONS regex
Unknown charname 'e_ACUTE' at
########
-# alias with file OK but file has :short aliasses
+# alias with file OK but file has :short aliases
--FILE-- ../../lib/unicore/xyzzy_alias.pl
#!perl
( e_ACUTE => "LATIN:e WITH ACUTE",
OPTIONS regex
$
########
-# alias with :short and file OK has :long aliasses
+# alias with :short and file OK has :long aliases
--FILE-- ../../lib/unicore/xyzzy_alias.pl
#!perl
( e_ACUTE => "LATIN SMALL LETTER E WITH ACUTE",
OPTIONS regex
Unknown charname 'LATIN SMALL LETTER E WITH ACUTE' at
########
-# alias with file implicit :full but file has :short aliasses
+# alias with file implicit :full but file has :short aliases
--FILE-- ../../lib/unicore/xyzzy_alias.pl
#!perl
( e_ACUTE => "LATIN:e WITH ACUTE",
OPTIONS regex
Unknown charname 'LATIN:e WITH ACUTE' at
########
-# alias with file implicit :full and file has :long aliasses
+# alias with file implicit :full and file has :long aliases
--FILE-- ../../lib/unicore/xyzzy_alias.pl
#!perl
( e_ACUTE => "LATIN SMALL LETTER E WITH ACUTE",
Global symbol "$foo" requires explicit package name at (re_eval 1) line 1.
Compilation failed in regexp at - line 3.
########
-# [perl #73712] 'Variable is not imported' should be suppressable
+# [perl #73712] 'Variable is not imported' should be suppressible
$dweck;
use strict 'vars';
no warnings;
# toke.c
use warnings 'misc';
use subs qw/dump/;
-sub dump { print "no warning for overriden dump\n"; }
+sub dump { print "no warning for overridden dump\n"; }
dump;
EXPECT
-no warning for overriden dump
+no warning for overridden dump
########
# toke.c
use warnings 'ambiguous';
[utf16_to_utf8]
Malformed UTF-16 surrogate
- <<<<<< Add a test when somethig actually calls utf16_to_utf8
+ <<<<<< Add a test when something actually calls utf16_to_utf8
__END__
# utf8.c [utf8_to_uv] -W
ok(!mro::is_universal('MRO_B'));
# is_universal, get_mro, and get_linear_isa should
-# handle non-existant packages sanely
+# handle non-existent packages sanely
ok(!mro::is_universal('Does_Not_Exist'));
is(mro::get_mro('Also_Does_Not_Exist'), 'dfs');
ok(eq_array(
=pod
-This tests the classic diamond inheritence pattern.
+This tests the classic diamond inheritance pattern.
<A>
/ \
=pod
-This tests the classic diamond inheritence pattern.
+This tests the classic diamond inheritance pattern.
<A>
/ \
can_ok($bar, 'bar');
my $value = eval { $bar->bar() };
- ok(!$@, '... calling bar() succedded') || diag $@;
+ ok(!$@, '... calling bar() succeeded') || diag $@;
is($value, 'Foo::bar', '... got the right return value too');
}
=pod
-This tests the classic diamond inheritence pattern.
+This tests the classic diamond inheritance pattern.
<A>
/ \
=pod
-This tests the classic diamond inheritence pattern.
+This tests the classic diamond inheritance pattern.
<A>
/ \
}
ok(!mro::get_pkg_gen('ReallyDoesNotExist'),
- "pkg_gen 0 for non-existant pkg");
+ "pkg_gen 0 for non-existent pkg");
my $f_gen = mro::get_pkg_gen('Foo');
ok($f_gen > 0, 'Foo pkg_gen > 0');
our @ISA = qw//;
}
-# A series of 8 abberations that would cause infinite loops,
+# A series of 8 aberations that would cause infinite loops,
# each one undoing the work of the previous
my @loopies = (
sub { @E::ISA = qw/F/ },
our @ISA = qw//;
}
-# A series of 8 abberations that would cause infinite loops,
+# A series of 8 aberations that would cause infinite loops,
# each one undoing the work of the previous
my @loopies = (
sub { @E::ISA = qw/F/ },
'PVBMs don\'t segfault attributes::get';
{
- # [perl #49472] Attributes + Unkown Error
+ # [perl #49472] Attributes + Unknown Error
eval '
use strict;
sub MODIFY_CODE_ATTRIBUTE{}
$prog =~ s/\@\@\@\@/$filename/;
-fresh_perl_is("require AnyDBM_File;\n$prog", 'ok', {}, 'explict require');
+fresh_perl_is("require AnyDBM_File;\n$prog", 'ok', {}, 'explicit require');
fresh_perl_is($prog, 'ok', {}, 'implicit require');
$prog = <<'EOC';
print "not " if (length $@ != 0);
print "ok $test # length of \$@ after eval\n"; $test++;
-# Check if eval { 1 }; compeltly resets $@
+# Check if eval { 1 }; completely resets $@
if (eval "use Devel::Peek; 1;") {
$tempfile = tempfile();
$outfile = tempfile();
my $ok = runperl(progfile => $tempfile);
print "not " unless $ok;
- print "ok $test # eval { 1 } completly resets \$@\n";
+ print "ok $test # eval { 1 } completely resets \$@\n";
}
else {
- print "ok $test # skipped - eval { 1 } completly resets \$@\n";
+ print "ok $test # skipped - eval { 1 } completely resets \$@\n";
}
$test++;
}
-# supress VMS whinging about bad execs.
+# suppress VMS whinging about bad execs.
use vmsish qw(hushed);
$| = 1; # flush stdout
}
{
- # This shouldn't loop indefinitively.
+ # This shouldn't loop indefinitely.
my @empty = map { while (1) {} } ();
cmp_ok("@empty", 'eq', '', 'staying alive');
}
is (ref $::{oonk}, 'SCALAR', "Export doesn't affect original");
is (eval 'ga_shloip', "Value", "Constant has correct value");
is (ref $::{ga_shloip}, 'SCALAR',
- "Inlining of constant doesn't change represenatation");
+ "Inlining of constant doesn't change representation");
delete $::{ga_shloip};
$::{BONK} = \"powie";
*{"BONK"} = \&{"BONK"};
eval 'is(BONK(), "powie",
- "Assigment works when glob created midway (bug 45607)"); 1'
+ "Assignment works when glob created midway (bug 45607)"); 1'
or die $@;
}
local $SIG{__WARN__} = sub { $warn = $_[0] };
use warnings;
my $str = "$glob";
- is($warn, '', "RT #60954 anon glob stringification shouln't warn");
+ is($warn, '', "RT #60954 anon glob stringification shouldn't warn");
is($str, '', "RT #60954 anon glob stringification should be empty");
}
do \"pass\n(\n'Scalar references are treated as initial file contents'\n)\n"
or die;
-open $fh, "<", \"ss('The file is concatentated');";
+open $fh, "<", \"ss('The file is concatenated');";
do [\'pa', $fh] or die;
for ("implicit foo") { # implicit "my $_"
ok( $_ eq "implicit foo", 'for implicit my $_' );
/(.)/;
- ok( $1 eq "i", '...m// in for implicity my $_' );
+ ok( $1 eq "i", '...m// in for implicit my $_' );
ok( our $_ eq 'global', '...our $_ inside for implicit my $_' );
}
ok( $_ eq 'local', '...my $_ restored outside for implicit my $_' );
# Also need to cope with %g notation for max_uv_p1 that actually gives an
# integer less than max_uv because of correct rounding for the limited
-# precisision. This bites for 12 byte long doubles and 8 byte UVs
+# precision. This bites for 12 byte long doubles and 8 byte UVs
my $temp = $max_uv_p1;
my $max_uv_p1_as_iv;
::is( qx/cp/, "11 cp", 'qx' );
}
-# Verify that the parsing of overriden keywords isn't messed up
+# Verify that the parsing of overridden keywords isn't messed up
# by the indirect object notation
{
local $SIG{__WARN__} = sub {
numbers_with_total ('q', -1,
-9223372036854775808, -1, 0, 1,9223372036854775807);
# This total is icky, but the true total is 2**65-1, and need a way to generate
-# the epxected checksum on any system including those where NVs can preserve
+# the expected checksum on any system including those where NVs can preserve
# 65 bits. (long double is 128 bits on sparc, so they certainly can)
# or where rounding is down not up on binary conversion (crays)
numbers_with_total ('Q', sub {
{ local $x }
is(pos($x), 4);
-# Explict test that triggers the utf8_mg_len_cache_update() code path in
+# Explicit test that triggers the utf8_mg_len_cache_update() code path in
# Perl_sv_pos_b2u().
$x = "\x{100}BC";
require './test.pl';
}
-# This calcualtion ought to be within 0.001 of the right answer.
+# This calculation ought to be within 0.001 of the right answer.
my $bits_in_uv = int (0.001 + log (~0+1) / log 2);
# 3**30 < 2**48, don't trust things outside that range on a Cray
# to find out what's wrong with your rand. Or with this
# algorithm. :-)
#
- # Calculating absoulute standard deviation for number of bits set
+ # Calculating absolute standard deviation for number of bits set
# (eight bits per rep)
$dev = abs ($bits - $reps * 4) / sqrt($reps * 2);
ok($@, 'Lower bound rejected: ' . -$ii);
}
-# double/tripple magic tests
+# double/triple magic tests
sub TIESCALAR { bless { value => $_[1], orig => $_[1] } }
sub STORE { $_[0]{store}++; $_[0]{value} = $_[1] }
sub FETCH { $_[0]{fetch}++; $_[0]{value} }
# GV => blessed(AV) => RV => GV => blessed(SV)
# all with a refcnt of 1, and hope that the second GV gets processed first
# by do_clean_named_objs. Then when the first GV is processed, it mustn't
-# find anything nastly left by the previous GV processing.
+# find anything nasty left by the previous GV processing.
# The eval is stop things in the main body of the code holding a reference
# to a GV, and the print at the end seems to bee necessary to ensure
# the correct freeing order of *x and *y (no, I don't know why - DAPM).
ok(-d -r _ , "chained -x's on dirhandle");
ok(-d DIR, "-d on a dirhandle works");
- # And now for the ambigious bareword case
+ # And now for the ambiguous bareword case
{
no warnings 'deprecated';
ok(open(DIR, "TEST"), 'Can open "TEST" dir')
ok(-d _ , "The special file handle _ is set correctly");
ok(-d -r *DIR{IO} , "chained -x's on *DIR{IO}");
- # And now for the ambigious bareword case
+ # And now for the ambiguous bareword case
{
no warnings 'deprecated';
ok(open(DIR, "TEST"), 'Can open "TEST" dir')
# when the args were tainted. This only occured on the first use of
# sprintf; after that, its TARG has taint magic attached, so setmagic
# at the end works. That's why there are multiple sprintf's below, rather
-# than just one wrapped in an inner loop. Also, any plantext betwerrn
+# than just one wrapped in an inner loop. Also, any plaintext between
# fprmat entires would correctly cause tainting to get set. so test with
# "%s%s" rather than eg "%s %s".
# the seen_evals field of a regexp was getting zeroed on clone, so
-# within a thread it didn't know that a regex object contrained a 'safe'
+# within a thread it didn't know that a regex object contained a 'safe'
# re_eval expression, so it later died with 'Eval-group not allowed' when
# you tried to interpolate the object
# Test case from perlmonks by runrig
# http://www.perlmonks.org/index.pl?node_id=273490
# "Here is what I tried. I think its similar to what you've tried
-# above. Its odd but convienient that after untie'ing you are left with
+# above. Its odd but convenient that after untie'ing you are left with
# a variable that has the same value as was last returned from
# FETCH. (At least on my perl v5.6.1). So you don't need to pass a
# reference to the variable in order to set it after the untie (here it
"\x{1ff}" => 0x1ff,
);
-# Check that we can find the 8-bit things by various litterals
+# Check that we can find the 8-bit things by various literals
is($hash8{"\x{00ff}"},0xFF);
is($hash8{"\x{007f}"},0x7F);
is($hash8{"\xff"},0xFF);
unless (-d 't' && -f 'MANIFEST') {
# we'll assume that we are in t then.
- # All files are interal to perl, so Unix-style is sufficiently portable.
+ # All files are internal to perl, so Unix-style is sufficiently portable.
$prefix = '../';
}
}
}
}
-# Lists all missing things as of the inaguration of this script, so we
+# Lists all missing things as of the inauguration of this script, so we
# don't have to go from "meh" to perfect all at once.
#
# PLEASE DO NOT ADD TO THIS LIST. Instead, write an entry in
safe_globals();
$why =~ s/\n.*//s;
$why .= "; Bug $BugId" if defined $BugId;
- # seems like the new harness code doesnt like todo and skip to be mixed.
+ # seems like the new harness code doesn't like todo and skip to be mixed.
# which seems like a bug in the harness to me. -- dmq
#$why .= " # TODO $TODO" if defined $TODO;
$::reg_infty = $Config {reg_infty} // 32767;
$::reg_infty_m = $::reg_infty - 1;
$::reg_infty_p = $::reg_infty + 1;
- $::reg_infty_m = $::reg_infty_m; # Surpress warning.
+ $::reg_infty_m = $::reg_infty_m; # Suppress warning.
# As well as failing if the pattern matches do unexpected things, the
# next three tests will fail if you should have picked up a lower-than-
}
{
my $n= 50;
- # this must be a high number and go from 0 to N, as the bug we are looking for doesnt
+ # this must be a high number and go from 0 to N, as the bug we are looking for doesn't
# seem to be predictable. Slight changes to the test make it fail earlier or later.
foreach my $i (0 .. $n)
{
my $str= "\n" x $i;
- ok $str=~/.*\z/, "implict MBOL check string disable does not break things length=$i";
+ ok $str=~/.*\z/, "implicit MBOL check string disable does not break things length=$i";
}
}
{
# (without the string eval the test script might be unparseable)
# Note: these test check the behaviour that currently is valid syntax
- # If a new regex modifier is added and a test fails then there is a backwards-compatibilty issue
+ # If a new regex modifier is added and a test fails then there is a backwards-compatibility issue
# Note-2: a new deprecate warning was added for this with commit e6897b1a5db0410e387ccbf677e89fc4a1d8c97a
# which indicate that this syntax will be removed in 5.16.
# When this happens the tests can be removed
{ # TRIE related
our @got = ();
"words" =~ /(word|word|word)(?{push @got, $1})s$/;
- iseq @got, 1, "TRIE optimation";
+ iseq @got, 1, "TRIE optimisation";
@got = ();
"words" =~ /(word|word|word)(?{push @got,$1})s$/i;
my @notIsPunct = grep {/[[:punct:]]/ and not /\p{IsPunct}/}
map {chr} 0x20 .. 0x7f;
iseq join ('', @notIsPunct), '$+<=>^`|~',
- '[:punct:] disagress with IsPunct on Symbols';
+ '[:punct:] disagrees with IsPunct on Symbols';
my @isPrint = grep {not /[[:print:]]/ and /\p{IsPrint}/}
map {chr} 0 .. 0x1f, 0x7f .. 0x9f;
{
local $BugId = '20000731.001';
ok "A \x{263a} B z C" =~ /A . B (??{ "z" }) C/,
- "Match UTF-8 char in presense of (??{ })";
+ "Match UTF-8 char in presence of (??{ })";
}
my @words = ('word1', 'word3', 'word5');
my $count;
foreach my $word (@words) {
- $text =~ s/$word\s//gi; # Leave a space to seperate words
+ $text =~ s/$word\s//gi; # Leave a space to separate words
# in the resultant str.
# The following block is not working.
if ($&) {
}
print "1..1\n";
-# there is an equivelent test in t/re/pat.t which does NOT fail
-# its not clear why it doesnt fail, so this todo gets its own test
+# there is an equivalent test in t/re/pat.t which does NOT fail
+# its not clear why it doesn't fail, so this todo gets its own test
# file until we can work it out.
my $x;
for my $study ('', 'study $subject', 'utf8::upgrade($subject)',
'utf8::upgrade($subject); study $subject') {
- # Need to make a copy, else the utf8::upgrade of an alreay studied
+ # Need to make a copy, else the utf8::upgrade of an already studied
# scalar confuses things.
my $subject = $subject;
my $c = $iters;
use strict;
use warnings;
-# This is just a wrapper for a generated file. Asssumes being run from 't'
+# This is just a wrapper for a generated file. Assumes being run from 't'
# directory
do '../lib/unicore/TestProp.pl';
}
EXPECT
It's good! >A< >B<
-######## [perl #8760] strangness with utf8 and warn
+######## [perl #8760] strangeness with utf8 and warn
$_="foo";utf8::upgrade($_);/bar/i,warn$_;
EXPECT
foo at - line 1.
$TODO ? _print(@mess) : _print_stderr(@mess);
}
-# Use this instead of "print STDERR" when outputing failure diagnostic
+# Use this instead of "print STDERR" when outputting failure diagnostic
# messages
sub diag {
_diag(@_);
}
-# Use this instead of "print" when outputing informational messages
+# Use this instead of "print" when outputting informational messages
sub note {
return unless @_;
_print( _comment(@_) );
}
unless ($pass) {
# It seems Irix long doubles can have 2147483648 and 2147483648
- # that stringify to the same thing but are acutally numerically
+ # that stringify to the same thing but are actually numerically
# different. Display the numbers if $type isn't a string operator,
# and the numbers are stringwise the same.
# (all string operators have alphabetic names, so tr/a-z// is true)
- # This will also show numbers for some uneeded cases, but will
- # definately be helpful for things such as == and <= that fail
+ # This will also show numbers for some unneeded cases, but will
+ # definitely be helpful for things such as == and <= that fail
if ($got eq $expected and $type !~ tr/a-z//) {
unshift @mess, "# $got - $expected = " . ($got - $expected) . "\n";
}
} elsif (defined $args{progfile}) {
$runperl = $runperl . qq( "$args{progfile}");
} else {
- # You probaby didn't want to be sucking in from the upstream stdin
+ # You probably didn't want to be sucking in from the upstream stdin
die "test.pl:runperl(): none of prog, progs, progfile, args, "
. " switches or stdin specified"
unless defined $args{args} or defined $args{switches}
my $s2p = File::Spec->catfile( File::Spec->updir(), 'x2p', 's2p' );
my $psed = File::Spec->catfile( File::Spec->curdir(), 'psed' );
if ($^O eq 'VMS') {
- # default in the .com extenson if it's not already there
+ # default in the .com extension if it's not already there
$s2p = VMS::Filespec::vmsify($s2p);
$psed = VMS::Filespec::vmsify($psed);
# Converting file specs from Unix format to VMS with the extended