xref: /onnv-gate/usr/src/cmd/perl/5.8.4/distrib/lib/constant.pm (revision 0:68f95e015346)
1*0Sstevel@tonic-gatepackage constant;
2*0Sstevel@tonic-gate
3*0Sstevel@tonic-gateuse strict;
4*0Sstevel@tonic-gateuse 5.006_00;
5*0Sstevel@tonic-gateuse warnings::register;
6*0Sstevel@tonic-gate
7*0Sstevel@tonic-gateour($VERSION, %declared);
8*0Sstevel@tonic-gate$VERSION = '1.04';
9*0Sstevel@tonic-gate
10*0Sstevel@tonic-gate#=======================================================================
11*0Sstevel@tonic-gate
12*0Sstevel@tonic-gate# Some names are evil choices.
13*0Sstevel@tonic-gatemy %keywords = map +($_, 1), qw{ BEGIN INIT CHECK END DESTROY AUTOLOAD };
14*0Sstevel@tonic-gate
15*0Sstevel@tonic-gatemy %forced_into_main = map +($_, 1),
16*0Sstevel@tonic-gate    qw{ STDIN STDOUT STDERR ARGV ARGVOUT ENV INC SIG };
17*0Sstevel@tonic-gate
18*0Sstevel@tonic-gatemy %forbidden = (%keywords, %forced_into_main);
19*0Sstevel@tonic-gate
20*0Sstevel@tonic-gate#=======================================================================
21*0Sstevel@tonic-gate# import() - import symbols into user's namespace
22*0Sstevel@tonic-gate#
23*0Sstevel@tonic-gate# What we actually do is define a function in the caller's namespace
24*0Sstevel@tonic-gate# which returns the value. The function we create will normally
25*0Sstevel@tonic-gate# be inlined as a constant, thereby avoiding further sub calling
26*0Sstevel@tonic-gate# overhead.
27*0Sstevel@tonic-gate#=======================================================================
28*0Sstevel@tonic-gatesub import {
29*0Sstevel@tonic-gate    my $class = shift;
30*0Sstevel@tonic-gate    return unless @_;			# Ignore 'use constant;'
31*0Sstevel@tonic-gate    my %constants = ();
32*0Sstevel@tonic-gate    my $multiple  = ref $_[0];
33*0Sstevel@tonic-gate
34*0Sstevel@tonic-gate    if ( $multiple ) {
35*0Sstevel@tonic-gate	if (ref $_[0] ne 'HASH') {
36*0Sstevel@tonic-gate	    require Carp;
37*0Sstevel@tonic-gate	    Carp::croak("Invalid reference type '".ref(shift)."' not 'HASH'");
38*0Sstevel@tonic-gate	}
39*0Sstevel@tonic-gate	%constants = %{+shift};
40*0Sstevel@tonic-gate    } else {
41*0Sstevel@tonic-gate	$constants{+shift} = undef;
42*0Sstevel@tonic-gate    }
43*0Sstevel@tonic-gate
44*0Sstevel@tonic-gate    foreach my $name ( keys %constants ) {
45*0Sstevel@tonic-gate	unless (defined $name) {
46*0Sstevel@tonic-gate	    require Carp;
47*0Sstevel@tonic-gate	    Carp::croak("Can't use undef as constant name");
48*0Sstevel@tonic-gate	}
49*0Sstevel@tonic-gate	my $pkg = caller;
50*0Sstevel@tonic-gate
51*0Sstevel@tonic-gate	# Normal constant name
52*0Sstevel@tonic-gate	if ($name =~ /^_?[^\W_0-9]\w*\z/ and !$forbidden{$name}) {
53*0Sstevel@tonic-gate	    # Everything is okay
54*0Sstevel@tonic-gate
55*0Sstevel@tonic-gate	# Name forced into main, but we're not in main. Fatal.
56*0Sstevel@tonic-gate	} elsif ($forced_into_main{$name} and $pkg ne 'main') {
57*0Sstevel@tonic-gate	    require Carp;
58*0Sstevel@tonic-gate	    Carp::croak("Constant name '$name' is forced into main::");
59*0Sstevel@tonic-gate
60*0Sstevel@tonic-gate	# Starts with double underscore. Fatal.
61*0Sstevel@tonic-gate	} elsif ($name =~ /^__/) {
62*0Sstevel@tonic-gate	    require Carp;
63*0Sstevel@tonic-gate	    Carp::croak("Constant name '$name' begins with '__'");
64*0Sstevel@tonic-gate
65*0Sstevel@tonic-gate	# Maybe the name is tolerable
66*0Sstevel@tonic-gate	} elsif ($name =~ /^[A-Za-z_]\w*\z/) {
67*0Sstevel@tonic-gate	    # Then we'll warn only if you've asked for warnings
68*0Sstevel@tonic-gate	    if (warnings::enabled()) {
69*0Sstevel@tonic-gate		if ($keywords{$name}) {
70*0Sstevel@tonic-gate		    warnings::warn("Constant name '$name' is a Perl keyword");
71*0Sstevel@tonic-gate		} elsif ($forced_into_main{$name}) {
72*0Sstevel@tonic-gate		    warnings::warn("Constant name '$name' is " .
73*0Sstevel@tonic-gate			"forced into package main::");
74*0Sstevel@tonic-gate		} else {
75*0Sstevel@tonic-gate		    # Catch-all - what did I miss? If you get this error,
76*0Sstevel@tonic-gate		    # please let me know what your constant's name was.
77*0Sstevel@tonic-gate		    # Write to <rootbeer@redcat.com>. Thanks!
78*0Sstevel@tonic-gate		    warnings::warn("Constant name '$name' has unknown problems");
79*0Sstevel@tonic-gate		}
80*0Sstevel@tonic-gate	    }
81*0Sstevel@tonic-gate
82*0Sstevel@tonic-gate	# Looks like a boolean
83*0Sstevel@tonic-gate	# use constant FRED == fred;
84*0Sstevel@tonic-gate	} elsif ($name =~ /^[01]?\z/) {
85*0Sstevel@tonic-gate            require Carp;
86*0Sstevel@tonic-gate	    if (@_) {
87*0Sstevel@tonic-gate		Carp::croak("Constant name '$name' is invalid");
88*0Sstevel@tonic-gate	    } else {
89*0Sstevel@tonic-gate		Carp::croak("Constant name looks like boolean value");
90*0Sstevel@tonic-gate	    }
91*0Sstevel@tonic-gate
92*0Sstevel@tonic-gate	} else {
93*0Sstevel@tonic-gate	   # Must have bad characters
94*0Sstevel@tonic-gate            require Carp;
95*0Sstevel@tonic-gate	    Carp::croak("Constant name '$name' has invalid characters");
96*0Sstevel@tonic-gate	}
97*0Sstevel@tonic-gate
98*0Sstevel@tonic-gate	{
99*0Sstevel@tonic-gate	    no strict 'refs';
100*0Sstevel@tonic-gate	    my $full_name = "${pkg}::$name";
101*0Sstevel@tonic-gate	    $declared{$full_name}++;
102*0Sstevel@tonic-gate	    if ($multiple) {
103*0Sstevel@tonic-gate		my $scalar = $constants{$name};
104*0Sstevel@tonic-gate		*$full_name = sub () { $scalar };
105*0Sstevel@tonic-gate	    } else {
106*0Sstevel@tonic-gate		if (@_ == 1) {
107*0Sstevel@tonic-gate		    my $scalar = $_[0];
108*0Sstevel@tonic-gate		    *$full_name = sub () { $scalar };
109*0Sstevel@tonic-gate		} elsif (@_) {
110*0Sstevel@tonic-gate		    my @list = @_;
111*0Sstevel@tonic-gate		    *$full_name = sub () { @list };
112*0Sstevel@tonic-gate		} else {
113*0Sstevel@tonic-gate		    *$full_name = sub () { };
114*0Sstevel@tonic-gate		}
115*0Sstevel@tonic-gate	    }
116*0Sstevel@tonic-gate	}
117*0Sstevel@tonic-gate    }
118*0Sstevel@tonic-gate}
119*0Sstevel@tonic-gate
120*0Sstevel@tonic-gate1;
121*0Sstevel@tonic-gate
122*0Sstevel@tonic-gate__END__
123*0Sstevel@tonic-gate
124*0Sstevel@tonic-gate=head1 NAME
125*0Sstevel@tonic-gate
126*0Sstevel@tonic-gateconstant - Perl pragma to declare constants
127*0Sstevel@tonic-gate
128*0Sstevel@tonic-gate=head1 SYNOPSIS
129*0Sstevel@tonic-gate
130*0Sstevel@tonic-gate    use constant PI    => 4 * atan2(1, 1);
131*0Sstevel@tonic-gate    use constant DEBUG => 0;
132*0Sstevel@tonic-gate
133*0Sstevel@tonic-gate    print "Pi equals ", PI, "...\n" if DEBUG;
134*0Sstevel@tonic-gate
135*0Sstevel@tonic-gate    use constant {
136*0Sstevel@tonic-gate        SEC   => 0,
137*0Sstevel@tonic-gate        MIN   => 1,
138*0Sstevel@tonic-gate        HOUR  => 2,
139*0Sstevel@tonic-gate        MDAY  => 3,
140*0Sstevel@tonic-gate        MON   => 4,
141*0Sstevel@tonic-gate        YEAR  => 5,
142*0Sstevel@tonic-gate        WDAY  => 6,
143*0Sstevel@tonic-gate        YDAY  => 7,
144*0Sstevel@tonic-gate        ISDST => 8,
145*0Sstevel@tonic-gate    };
146*0Sstevel@tonic-gate
147*0Sstevel@tonic-gate    use constant WEEKDAYS => qw(
148*0Sstevel@tonic-gate        Sunday Monday Tuesday Wednesday Thursday Friday Saturday
149*0Sstevel@tonic-gate    );
150*0Sstevel@tonic-gate
151*0Sstevel@tonic-gate    print "Today is ", (WEEKDAYS)[ (localtime)[WDAY] ], ".\n";
152*0Sstevel@tonic-gate
153*0Sstevel@tonic-gate=head1 DESCRIPTION
154*0Sstevel@tonic-gate
155*0Sstevel@tonic-gateThis will declare a symbol to be a constant with the given value.
156*0Sstevel@tonic-gate
157*0Sstevel@tonic-gateWhen you declare a constant such as C<PI> using the method shown
158*0Sstevel@tonic-gateabove, each machine your script runs upon can have as many digits
159*0Sstevel@tonic-gateof accuracy as it can use. Also, your program will be easier to
160*0Sstevel@tonic-gateread, more likely to be maintained (and maintained correctly), and
161*0Sstevel@tonic-gatefar less likely to send a space probe to the wrong planet because
162*0Sstevel@tonic-gatenobody noticed the one equation in which you wrote C<3.14195>.
163*0Sstevel@tonic-gate
164*0Sstevel@tonic-gateWhen a constant is used in an expression, perl replaces it with its
165*0Sstevel@tonic-gatevalue at compile time, and may then optimize the expression further.
166*0Sstevel@tonic-gateIn particular, any code in an C<if (CONSTANT)> block will be optimized
167*0Sstevel@tonic-gateaway if the constant is false.
168*0Sstevel@tonic-gate
169*0Sstevel@tonic-gate=head1 NOTES
170*0Sstevel@tonic-gate
171*0Sstevel@tonic-gateAs with all C<use> directives, defining a constant happens at
172*0Sstevel@tonic-gatecompile time. Thus, it's probably not correct to put a constant
173*0Sstevel@tonic-gatedeclaration inside of a conditional statement (like C<if ($foo)
174*0Sstevel@tonic-gate{ use constant ... }>).
175*0Sstevel@tonic-gate
176*0Sstevel@tonic-gateConstants defined using this module cannot be interpolated into
177*0Sstevel@tonic-gatestrings like variables.  However, concatenation works just fine:
178*0Sstevel@tonic-gate
179*0Sstevel@tonic-gate    print "Pi equals PI...\n";        # WRONG: does not expand "PI"
180*0Sstevel@tonic-gate    print "Pi equals ".PI."...\n";    # right
181*0Sstevel@tonic-gate
182*0Sstevel@tonic-gateEven though a reference may be declared as a constant, the reference may
183*0Sstevel@tonic-gatepoint to data which may be changed, as this code shows.
184*0Sstevel@tonic-gate
185*0Sstevel@tonic-gate    use constant ARRAY => [ 1,2,3,4 ];
186*0Sstevel@tonic-gate    print ARRAY->[1];
187*0Sstevel@tonic-gate    ARRAY->[1] = " be changed";
188*0Sstevel@tonic-gate    print ARRAY->[1];
189*0Sstevel@tonic-gate
190*0Sstevel@tonic-gateDereferencing constant references incorrectly (such as using an array
191*0Sstevel@tonic-gatesubscript on a constant hash reference, or vice versa) will be trapped at
192*0Sstevel@tonic-gatecompile time.
193*0Sstevel@tonic-gate
194*0Sstevel@tonic-gateConstants belong to the package they are defined in.  To refer to a
195*0Sstevel@tonic-gateconstant defined in another package, specify the full package name, as
196*0Sstevel@tonic-gatein C<Some::Package::CONSTANT>.  Constants may be exported by modules,
197*0Sstevel@tonic-gateand may also be called as either class or instance methods, that is,
198*0Sstevel@tonic-gateas C<< Some::Package->CONSTANT >> or as C<< $obj->CONSTANT >> where
199*0Sstevel@tonic-gateC<$obj> is an instance of C<Some::Package>.  Subclasses may define
200*0Sstevel@tonic-gatetheir own constants to override those in their base class.
201*0Sstevel@tonic-gate
202*0Sstevel@tonic-gateThe use of all caps for constant names is merely a convention,
203*0Sstevel@tonic-gatealthough it is recommended in order to make constants stand out
204*0Sstevel@tonic-gateand to help avoid collisions with other barewords, keywords, and
205*0Sstevel@tonic-gatesubroutine names. Constant names must begin with a letter or
206*0Sstevel@tonic-gateunderscore. Names beginning with a double underscore are reserved. Some
207*0Sstevel@tonic-gatepoor choices for names will generate warnings, if warnings are enabled at
208*0Sstevel@tonic-gatecompile time.
209*0Sstevel@tonic-gate
210*0Sstevel@tonic-gate=head2 List constants
211*0Sstevel@tonic-gate
212*0Sstevel@tonic-gateConstants may be lists of more (or less) than one value.  A constant
213*0Sstevel@tonic-gatewith no values evaluates to C<undef> in scalar context.  Note that
214*0Sstevel@tonic-gateconstants with more than one value do I<not> return their last value in
215*0Sstevel@tonic-gatescalar context as one might expect.  They currently return the number
216*0Sstevel@tonic-gateof values, but B<this may change in the future>.  Do not use constants
217*0Sstevel@tonic-gatewith multiple values in scalar context.
218*0Sstevel@tonic-gate
219*0Sstevel@tonic-gateB<NOTE:> This implies that the expression defining the value of a
220*0Sstevel@tonic-gateconstant is evaluated in list context.  This may produce surprises:
221*0Sstevel@tonic-gate
222*0Sstevel@tonic-gate    use constant TIMESTAMP => localtime;                # WRONG!
223*0Sstevel@tonic-gate    use constant TIMESTAMP => scalar localtime;         # right
224*0Sstevel@tonic-gate
225*0Sstevel@tonic-gateThe first line above defines C<TIMESTAMP> as a 9-element list, as
226*0Sstevel@tonic-gatereturned by localtime() in list context.  To set it to the string
227*0Sstevel@tonic-gatereturned by localtime() in scalar context, an explicit C<scalar>
228*0Sstevel@tonic-gatekeyword is required.
229*0Sstevel@tonic-gate
230*0Sstevel@tonic-gateList constants are lists, not arrays.  To index or slice them, they
231*0Sstevel@tonic-gatemust be placed in parentheses.
232*0Sstevel@tonic-gate
233*0Sstevel@tonic-gate    my @workdays = WEEKDAYS[1 .. 5];            # WRONG!
234*0Sstevel@tonic-gate    my @workdays = (WEEKDAYS)[1 .. 5];          # right
235*0Sstevel@tonic-gate
236*0Sstevel@tonic-gate=head2 Defining multiple constants at once
237*0Sstevel@tonic-gate
238*0Sstevel@tonic-gateInstead of writing multiple C<use constant> statements, you may define
239*0Sstevel@tonic-gatemultiple constants in a single statement by giving, instead of the
240*0Sstevel@tonic-gateconstant name, a reference to a hash where the keys are the names of
241*0Sstevel@tonic-gatethe constants to be defined.  Obviously, all constants defined using
242*0Sstevel@tonic-gatethis method must have a single value.
243*0Sstevel@tonic-gate
244*0Sstevel@tonic-gate    use constant {
245*0Sstevel@tonic-gate        FOO => "A single value",
246*0Sstevel@tonic-gate        BAR => "This", "won't", "work!",        # Error!
247*0Sstevel@tonic-gate    };
248*0Sstevel@tonic-gate
249*0Sstevel@tonic-gateThis is a fundamental limitation of the way hashes are constructed in
250*0Sstevel@tonic-gatePerl.  The error messages produced when this happens will often be
251*0Sstevel@tonic-gatequite cryptic -- in the worst case there may be none at all, and
252*0Sstevel@tonic-gateyou'll only later find that something is broken.
253*0Sstevel@tonic-gate
254*0Sstevel@tonic-gateWhen defining multiple constants, you cannot use the values of other
255*0Sstevel@tonic-gateconstants defined in the same declaration.  This is because the
256*0Sstevel@tonic-gatecalling package doesn't know about any constant within that group
257*0Sstevel@tonic-gateuntil I<after> the C<use> statement is finished.
258*0Sstevel@tonic-gate
259*0Sstevel@tonic-gate    use constant {
260*0Sstevel@tonic-gate        BITMASK => 0xAFBAEBA8,
261*0Sstevel@tonic-gate        NEGMASK => ~BITMASK,                    # Error!
262*0Sstevel@tonic-gate    };
263*0Sstevel@tonic-gate
264*0Sstevel@tonic-gate=head2 Magic constants
265*0Sstevel@tonic-gate
266*0Sstevel@tonic-gateMagical values and references can be made into constants at compile
267*0Sstevel@tonic-gatetime, allowing for way cool stuff like this.  (These error numbers
268*0Sstevel@tonic-gatearen't totally portable, alas.)
269*0Sstevel@tonic-gate
270*0Sstevel@tonic-gate    use constant E2BIG => ($! = 7);
271*0Sstevel@tonic-gate    print   E2BIG, "\n";        # something like "Arg list too long"
272*0Sstevel@tonic-gate    print 0+E2BIG, "\n";        # "7"
273*0Sstevel@tonic-gate
274*0Sstevel@tonic-gateYou can't produce a tied constant by giving a tied scalar as the
275*0Sstevel@tonic-gatevalue.  References to tied variables, however, can be used as
276*0Sstevel@tonic-gateconstants without any problems.
277*0Sstevel@tonic-gate
278*0Sstevel@tonic-gate=head1 TECHNICAL NOTES
279*0Sstevel@tonic-gate
280*0Sstevel@tonic-gateIn the current implementation, scalar constants are actually
281*0Sstevel@tonic-gateinlinable subroutines. As of version 5.004 of Perl, the appropriate
282*0Sstevel@tonic-gatescalar constant is inserted directly in place of some subroutine
283*0Sstevel@tonic-gatecalls, thereby saving the overhead of a subroutine call. See
284*0Sstevel@tonic-gateL<perlsub/"Constant Functions"> for details about how and when this
285*0Sstevel@tonic-gatehappens.
286*0Sstevel@tonic-gate
287*0Sstevel@tonic-gateIn the rare case in which you need to discover at run time whether a
288*0Sstevel@tonic-gateparticular constant has been declared via this module, you may use
289*0Sstevel@tonic-gatethis function to examine the hash C<%constant::declared>. If the given
290*0Sstevel@tonic-gateconstant name does not include a package name, the current package is
291*0Sstevel@tonic-gateused.
292*0Sstevel@tonic-gate
293*0Sstevel@tonic-gate    sub declared ($) {
294*0Sstevel@tonic-gate        use constant 1.01;              # don't omit this!
295*0Sstevel@tonic-gate        my $name = shift;
296*0Sstevel@tonic-gate        $name =~ s/^::/main::/;
297*0Sstevel@tonic-gate        my $pkg = caller;
298*0Sstevel@tonic-gate        my $full_name = $name =~ /::/ ? $name : "${pkg}::$name";
299*0Sstevel@tonic-gate        $constant::declared{$full_name};
300*0Sstevel@tonic-gate    }
301*0Sstevel@tonic-gate
302*0Sstevel@tonic-gate=head1 BUGS
303*0Sstevel@tonic-gate
304*0Sstevel@tonic-gateIn the current version of Perl, list constants are not inlined
305*0Sstevel@tonic-gateand some symbols may be redefined without generating a warning.
306*0Sstevel@tonic-gate
307*0Sstevel@tonic-gateIt is not possible to have a subroutine or a keyword with the same
308*0Sstevel@tonic-gatename as a constant in the same package. This is probably a Good Thing.
309*0Sstevel@tonic-gate
310*0Sstevel@tonic-gateA constant with a name in the list C<STDIN STDOUT STDERR ARGV ARGVOUT
311*0Sstevel@tonic-gateENV INC SIG> is not allowed anywhere but in package C<main::>, for
312*0Sstevel@tonic-gatetechnical reasons.
313*0Sstevel@tonic-gate
314*0Sstevel@tonic-gateUnlike constants in some languages, these cannot be overridden
315*0Sstevel@tonic-gateon the command line or via environment variables.
316*0Sstevel@tonic-gate
317*0Sstevel@tonic-gateYou can get into trouble if you use constants in a context which
318*0Sstevel@tonic-gateautomatically quotes barewords (as is true for any subroutine call).
319*0Sstevel@tonic-gateFor example, you can't say C<$hash{CONSTANT}> because C<CONSTANT> will
320*0Sstevel@tonic-gatebe interpreted as a string.  Use C<$hash{CONSTANT()}> or
321*0Sstevel@tonic-gateC<$hash{+CONSTANT}> to prevent the bareword quoting mechanism from
322*0Sstevel@tonic-gatekicking in.  Similarly, since the C<< => >> operator quotes a bareword
323*0Sstevel@tonic-gateimmediately to its left, you have to say C<< CONSTANT() => 'value' >>
324*0Sstevel@tonic-gate(or simply use a comma in place of the big arrow) instead of
325*0Sstevel@tonic-gateC<< CONSTANT => 'value' >>.
326*0Sstevel@tonic-gate
327*0Sstevel@tonic-gate=head1 AUTHOR
328*0Sstevel@tonic-gate
329*0Sstevel@tonic-gateTom Phoenix, E<lt>F<rootbeer@redcat.com>E<gt>, with help from
330*0Sstevel@tonic-gatemany other folks.
331*0Sstevel@tonic-gate
332*0Sstevel@tonic-gateMultiple constant declarations at once added by Casey West,
333*0Sstevel@tonic-gateE<lt>F<casey@geeknest.com>E<gt>.
334*0Sstevel@tonic-gate
335*0Sstevel@tonic-gateDocumentation mostly rewritten by Ilmari Karonen,
336*0Sstevel@tonic-gateE<lt>F<perl@itz.pp.sci.fi>E<gt>.
337*0Sstevel@tonic-gate
338*0Sstevel@tonic-gate=head1 COPYRIGHT
339*0Sstevel@tonic-gate
340*0Sstevel@tonic-gateCopyright (C) 1997, 1999 Tom Phoenix
341*0Sstevel@tonic-gate
342*0Sstevel@tonic-gateThis module is free software; you can redistribute it or modify it
343*0Sstevel@tonic-gateunder the same terms as Perl itself.
344*0Sstevel@tonic-gate
345*0Sstevel@tonic-gate=cut
346