xref: /openbsd-src/gnu/usr.bin/perl/configpm (revision 91f110e064cd7c194e59e019b83bb7496c1c84d4)
1#!./miniperl -w
2#
3# configpm
4#
5# Copyright (C) 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001,
6# 2002, 2003, 2004, 2005, 2006, 2007 Larry Wall and others.
7#
8#
9# Regenerate the files
10#
11#    lib/Config.pm
12#    lib/Config_heavy.pl
13#    lib/Config.pod
14#    lib/Cross.pm (optionally)
15#
16#
17# from the contents of the static files
18#
19#    Porting/Glossary
20#    myconfig.SH
21#
22# and from the contents of the Configure-generated file
23#
24#    config.sh
25#
26# Note that output directory is xlib/[cross-name]/ for cross-compiling
27#
28# It will only update Config.pm and Config_heavy.pl if the contents of
29# either file would be different. Note that *both* files are updated in
30# this case, since for example an extension makefile that has a dependency
31# on Config.pm should trigger even if only Config_heavy.pl has changed.
32
33sub usage { die <<EOF }
34usage: $0  [ options ]
35    --cross=PLATFORM    cross-compile for a different platform
36    --no-glossary       don't include Porting/Glossary in lib/Config.pod
37    --chdir=dir         change directory before writing files
38EOF
39
40use strict;
41use vars qw(%Config $Config_SH_expanded);
42
43my $how_many_common = 22;
44
45# commonly used names to precache (and hence lookup fastest)
46my %Common;
47
48while ($how_many_common--) {
49    $_ = <DATA>;
50    chomp;
51    /^(\S+):\s*(\d+)$/ or die "Malformed line '$_'";
52    $Common{$1} = $1;
53}
54
55# Post 37589e1eefb1bd62 DynaLoader defaults to reading these at runtime.
56# Ideally we're redo the data below, but Fotango's build system made it
57# wonderfully easy to instrument, and no longer exists.
58$Common{$_} = $_ foreach qw(dlext so);
59
60# names of things which may need to have slashes changed to double-colons
61my %Extensions = map {($_,$_)}
62                 qw(dynamic_ext static_ext extensions known_extensions);
63
64# The plan is that this information is used by ExtUtils::MakeMaker to generate
65# Makefile dependencies, rather than hardcoding a list, which has become out
66# of date. However, currently, MM_Unix.pm and MM_VMS.pm have *different* lists,
67# *and* descrip_mms.template doesn't actually install all the headers.
68# The "Unix" list seems to (attempt to) avoid the generated headers, which I'm
69# not sure is the right thing to do. Also, not certain whether it would be
70# easier to parse MANIFEST to get these (adding config.h, and potentially
71# removing others), but for now, stick to a hard coded list.
72
73# Could use a map to add ".h", but I suspect that it's easier to use literals,
74# so that anyone using grep will find them
75# This is the list from MM_VMS, plus pad.h, parser.h, perlsfio.h utf8.h
76# which it installs. It *doesn't* install perliol.h - FIXME.
77my @header_files = qw(EXTERN.h INTERN.h XSUB.h av.h config.h cop.h cv.h
78		      embed.h embedvar.h form.h gv.h handy.h hv.h intrpvar.h
79		      iperlsys.h keywords.h mg.h nostdio.h op.h opcode.h
80		      pad.h parser.h patchlevel.h perl.h perlio.h perlsdio.h
81		      perlsfio.h perlvars.h perly.h pp.h pp_proto.h proto.h
82		      regcomp.h regexp.h regnodes.h scope.h sv.h thread.h utf8.h
83		      util.h);
84
85# No point in adding fakethr.h, as it no longer works
86push @header_files,
87    $^O eq 'VMS' ? 'vmsish.h' : qw(dosish.h perliol.h time64.h unixish.h);
88
89my $header_files = '    return qw(' . join(' ', sort @header_files) . ');';
90$header_files =~ s/(?=.{64})   # If line is still overlength
91		   (.{1,64})\  # Split at the last convenient space
92		  /$1\n              /gx;
93
94# libpaths that should be truncated after the first path element
95my %Libpathtrunc = map {($_,$_)}
96                   qw(archlib archlibexp privlib privlibexp sitearch sitearchexp
97                      sitelib sitelibexp);
98
99# allowed opts as well as specifies default and initial values
100my %Allowed_Opts = (
101    'cross'    => '', # --cross=PLATFORM - crosscompiling for PLATFORM
102    'glossary' => 1,  # --no-glossary  - no glossary file inclusion,
103                      #                  for compactness
104    'chdir'    => '', # --chdir=dir    - change directory before writing files
105);
106
107sub opts {
108    # user specified options
109    my %given_opts = (
110        # --opt=smth
111        (map {/^--([\-_\w]+)=(.*)$/} @ARGV),
112        # --opt --no-opt --noopt
113        (map {/^no-?(.*)$/i?($1=>0):($_=>1)} map {/^--([\-_\w]+)$/} @ARGV),
114    );
115
116    my %opts = (%Allowed_Opts, %given_opts);
117
118    for my $opt (grep {!exists $Allowed_Opts{$_}} keys %given_opts) {
119        warn "option '$opt' is not recognized";
120	usage;
121    }
122    @ARGV = grep {!/^--/} @ARGV;
123
124    return %opts;
125}
126
127
128my %Opts = opts();
129
130if ($Opts{chdir}) {
131    chdir $Opts{chdir} or die "$0: could not chdir $Opts{chdir}: $!"
132}
133
134my ($Config_SH, $Config_PM, $Config_heavy, $Config_POD);
135my $Glossary = 'Porting/Glossary';
136
137if ($Opts{cross}) {
138  # creating cross-platform config file
139  mkdir "xlib";
140  mkdir "xlib/$Opts{cross}";
141  $Config_PM = "xlib/$Opts{cross}/Config.pm";
142  $Config_POD = "xlib/$Opts{cross}/Config.pod";
143  $Config_SH = "Cross/config-$Opts{cross}.sh";
144}
145else {
146  $Config_PM = "lib/Config.pm";
147  $Config_POD = "lib/Config.pod";
148  $Config_SH = "config.sh";
149}
150($Config_heavy = $Config_PM) =~ s/\.pm$/_heavy.pl/;
151die "Can't automatically determine name for Config_heavy.pl from '$Config_PM'"
152  if $Config_heavy eq $Config_PM;
153
154my $config_txt;
155my $heavy_txt;
156
157$heavy_txt .= <<'ENDOFBEG';
158# This file was created by configpm when Perl was built. Any changes
159# made to this file will be lost the next time perl is built.
160
161package Config;
162use strict;
163use warnings;
164use vars '%Config';
165
166sub bincompat_options {
167    return split ' ', (Internals::V())[0];
168}
169
170sub non_bincompat_options {
171    return split ' ', (Internals::V())[1];
172}
173
174sub compile_date {
175    return (Internals::V())[2]
176}
177
178sub local_patches {
179    my (undef, undef, undef, @patches) = Internals::V();
180    return @patches;
181}
182
183sub _V {
184    my ($bincompat, $non_bincompat, $date, @patches) = Internals::V();
185
186    my $opts = join ' ', sort split ' ', "$bincompat $non_bincompat";
187
188    # wrap at 76 columns.
189
190    $opts =~ s/(?=.{53})(.{1,53}) /$1\n                        /mg;
191
192    print Config::myconfig();
193    if ($^O eq 'VMS') {
194        print "\nCharacteristics of this PERLSHR image: \n";
195    } else {
196        print "\nCharacteristics of this binary (from libperl): \n";
197    }
198
199    print "  Compile-time options: $opts\n";
200
201    if (@patches) {
202        print "  Locally applied patches:\n";
203        print "\t$_\n" foreach @patches;
204    }
205
206    print "  Built under $^O\n";
207
208    print "  $date\n" if defined $date;
209
210    my @env = map { "$_=\"$ENV{$_}\"" } sort grep {/^PERL/} keys %ENV;
211    push @env, "CYGWIN=\"$ENV{CYGWIN}\"" if $^O eq 'cygwin' and $ENV{CYGWIN};
212
213    if (@env) {
214        print "  \%ENV:\n";
215        print "    $_\n" foreach @env;
216    }
217    print "  \@INC:\n";
218    print "    $_\n" foreach @INC;
219}
220
221sub header_files {
222ENDOFBEG
223
224$heavy_txt .= $header_files . "\n}\n\n";
225
226my $export_funcs = <<'EOT';
227my %Export_Cache = (myconfig => 1, config_sh => 1, config_vars => 1,
228		    config_re => 1, compile_date => 1, local_patches => 1,
229		    bincompat_options => 1, non_bincompat_options => 1,
230		    header_files => 1);
231EOT
232
233my %export_ok = eval $export_funcs or die;
234
235$config_txt .= sprintf << 'EOT', $export_funcs;
236# This file was created by configpm when Perl was built. Any changes
237# made to this file will be lost the next time perl is built.
238
239# for a description of the variables, please have a look at the
240# Glossary file, as written in the Porting folder, or use the url:
241# http://perl5.git.perl.org/perl.git/blob/HEAD:/Porting/Glossary
242
243package Config;
244use strict;
245use warnings;
246use vars '%%Config';
247
248# Skip @Config::EXPORT because it only contains %%Config, which we special
249# case below as it's not a function. @Config::EXPORT won't change in the
250# lifetime of Perl 5.
251%s
252@Config::EXPORT = qw(%%Config);
253@Config::EXPORT_OK = keys %%Export_Cache;
254
255# Need to stub all the functions to make code such as print Config::config_sh
256# keep working
257
258EOT
259
260$config_txt .= "sub $_;\n" foreach sort keys %export_ok;
261
262my $myver = sprintf "%vd", $^V;
263
264$config_txt .= sprintf <<'ENDOFBEG', ($myver) x 3;
265
266# Define our own import method to avoid pulling in the full Exporter:
267sub import {
268    shift;
269    @_ = @Config::EXPORT unless @_;
270
271    my @funcs = grep $_ ne '%%Config', @_;
272    my $export_Config = @funcs < @_ ? 1 : 0;
273
274    no strict 'refs';
275    my $callpkg = caller(0);
276    foreach my $func (@funcs) {
277	die qq{"$func" is not exported by the Config module\n}
278	    unless $Export_Cache{$func};
279	*{$callpkg.'::'.$func} = \&{$func};
280    }
281
282    *{"$callpkg\::Config"} = \%%Config if $export_Config;
283    return;
284}
285
286die "Perl lib version (%s) doesn't match executable '$0' version ($])"
287    unless $^V;
288
289$^V eq %s
290    or die "Perl lib version (%s) doesn't match executable '$0' version (" .
291	sprintf("v%%vd",$^V) . ")";
292
293ENDOFBEG
294
295
296my @non_v    = ();
297my @v_others = ();
298my $in_v     = 0;
299my %Data     = ();
300my $quote;
301
302
303my %seen_quotes;
304{
305  my ($name, $val);
306  open(CONFIG_SH, $Config_SH) || die "Can't open $Config_SH: $!";
307  while (<CONFIG_SH>) {
308    next if m:^#!/bin/sh:;
309
310    # Catch PERL_CONFIG_SH=true and PERL_VERSION=n line from Configure.
311    s/^(\w+)=(true|\d+)\s*$/$1='$2'\n/ or m/^(\w+)='(.*)'$/;
312    my($k, $v) = ($1, $2);
313
314    # grandfather PATCHLEVEL and SUBVERSION and CONFIG
315    if ($k) {
316	if ($k eq 'PERL_VERSION') {
317	    push @v_others, "PATCHLEVEL='$v'\n";
318	}
319	elsif ($k eq 'PERL_SUBVERSION') {
320	    push @v_others, "SUBVERSION='$v'\n";
321	}
322	elsif ($k eq 'PERL_CONFIG_SH') {
323	    push @v_others, "CONFIG='$v'\n";
324	}
325    }
326
327    # We can delimit things in config.sh with either ' or ".
328    unless ($in_v or m/^(\w+)=(['"])(.*\n)/){
329	push(@non_v, "#$_"); # not a name='value' line
330	next;
331    }
332    if ($in_v) {
333        $val .= $_;
334    }
335    else {
336	$quote = $2;
337        ($name,$val) = ($1,$3);
338    }
339    $in_v = $val !~ /$quote\n/;
340    next if $in_v;
341
342    # XXX - should use PERLLIB_SEP, not hard-code ':'
343    $val =~ s/^([^:]+).*${quote}\w*$/$1${quote}/ if $Libpathtrunc{$name};
344
345    s,/,::,g if $Extensions{$name};
346
347    $val =~ s/$quote\n?\z//;
348
349    my $line = "$name=$quote$val$quote\n";
350    push(@v_others, $line);
351    $seen_quotes{$quote}++;
352  }
353  close CONFIG_SH;
354}
355
356# This is somewhat grim, but I want the code for parsing config.sh here and
357# now so that I can expand $Config{ivsize} and $Config{ivtype}
358
359my $fetch_string = <<'EOT';
360
361# Search for it in the big string
362sub fetch_string {
363    my($self, $key) = @_;
364
365EOT
366
367if ($seen_quotes{'"'}) {
368    # We need the full ' and " code
369
370$fetch_string .= <<'EOT';
371    return undef unless my ($quote_type, $value) = $Config_SH_expanded =~ /\n$key=(['"])(.*?)\1\n/s;
372
373    # If we had a double-quote, we'd better eval it so escape
374    # sequences and such can be interpolated. Since the incoming
375    # value is supposed to follow shell rules and not perl rules,
376    # we escape any perl variable markers
377
378    # Historically, since " 'support' was added in change 1409, the
379    # interpolation was done before the undef. Stick to this arguably buggy
380    # behaviour as we're refactoring.
381    if ($quote_type eq '"') {
382	$value =~ s/\$/\\\$/g;
383	$value =~ s/\@/\\\@/g;
384	eval "\$value = \"$value\"";
385    }
386
387    # So we can say "if $Config{'foo'}".
388    $self->{$key} = $value eq 'undef' ? undef : $value; # cache it
389}
390EOT
391
392} else {
393    # We only have ' delimted.
394
395$fetch_string .= <<'EOT';
396    return undef unless $Config_SH_expanded =~ /\n$key=\'(.*?)\'\n/s;
397    # So we can say "if $Config{'foo'}".
398    $self->{$key} = $1 eq 'undef' ? undef : $1;
399}
400EOT
401
402}
403
404eval $fetch_string;
405die if $@;
406
407# Calculation for the keys for byteorder
408# This is somewhat grim, but I need to run fetch_string here.
409our $Config_SH_expanded = join "\n", '', @v_others;
410
411my $t = fetch_string ({}, 'ivtype');
412my $s = fetch_string ({}, 'ivsize');
413
414# byteorder does exist on its own but we overlay a virtual
415# dynamically recomputed value.
416
417# However, ivtype and ivsize will not vary for sane fat binaries
418
419my $f = $t eq 'long' ? 'L!' : $s == 8 ? 'Q': 'I';
420
421my $byteorder_code;
422if ($s == 4 || $s == 8) {
423    my $list = join ',', reverse(1..$s-1);
424    my $format = 'a'x$s;
425    $byteorder_code = <<"EOT";
426
427my \$i = ord($s);
428foreach my \$c ($list) { \$i <<= 8; \$i |= ord(\$c); }
429our \$byteorder = join('', unpack('$format', pack('$f', \$i)));
430EOT
431} else {
432    $byteorder_code = "our \$byteorder = '?'x$s;\n";
433}
434
435my @need_relocation;
436
437if (fetch_string({},'userelocatableinc')) {
438    foreach my $what (qw(prefixexp
439
440			 archlibexp
441			 html1direxp
442			 html3direxp
443			 man1direxp
444			 man3direxp
445			 privlibexp
446			 scriptdirexp
447			 sitearchexp
448			 sitebinexp
449			 sitehtml1direxp
450			 sitehtml3direxp
451			 sitelibexp
452			 siteman1direxp
453			 siteman3direxp
454			 sitescriptexp
455			 vendorarchexp
456			 vendorbinexp
457			 vendorhtml1direxp
458			 vendorhtml3direxp
459			 vendorlibexp
460			 vendorman1direxp
461			 vendorman3direxp
462			 vendorscriptexp
463
464			 siteprefixexp
465			 sitelib_stem
466			 vendorlib_stem
467
468			 installarchlib
469			 installhtml1dir
470			 installhtml3dir
471			 installman1dir
472			 installman3dir
473			 installprefix
474			 installprefixexp
475			 installprivlib
476			 installscript
477			 installsitearch
478			 installsitebin
479			 installsitehtml1dir
480			 installsitehtml3dir
481			 installsitelib
482			 installsiteman1dir
483			 installsiteman3dir
484			 installsitescript
485			 installvendorarch
486			 installvendorbin
487			 installvendorhtml1dir
488			 installvendorhtml3dir
489			 installvendorlib
490			 installvendorman1dir
491			 installvendorman3dir
492			 installvendorscript
493			 )) {
494	push @need_relocation, $what if fetch_string({}, $what) =~ m!^\.\.\./!;
495    }
496}
497
498my %need_relocation;
499@need_relocation{@need_relocation} = @need_relocation;
500
501# This can have .../ anywhere:
502if (fetch_string({}, 'otherlibdirs') =~ m!\.\.\./!) {
503    $need_relocation{otherlibdirs} = 'otherlibdirs';
504}
505
506my $relocation_code = <<'EOT';
507
508sub relocate_inc {
509  my $libdir = shift;
510  return $libdir unless $libdir =~ s!^\.\.\./!!;
511  my $prefix = $^X;
512  if ($prefix =~ s!/[^/]*$!!) {
513    while ($libdir =~ m!^\.\./!) {
514      # Loop while $libdir starts "../" and $prefix still has a trailing
515      # directory
516      last unless $prefix =~ s!/([^/]+)$!!;
517      # but bail out if the directory we picked off the end of $prefix is .
518      # or ..
519      if ($1 eq '.' or $1 eq '..') {
520	# Undo! This should be rare, hence code it this way rather than a
521	# check each time before the s!!! above.
522	$prefix = "$prefix/$1";
523	last;
524      }
525      # Remove that leading ../ and loop again
526      substr ($libdir, 0, 3, '');
527    }
528    $libdir = "$prefix/$libdir";
529  }
530  $libdir;
531}
532EOT
533
534if (%need_relocation) {
535  my $relocations_in_common;
536  # otherlibdirs only features in the hash
537  foreach (keys %need_relocation) {
538    $relocations_in_common++ if $Common{$_};
539  }
540  if ($relocations_in_common) {
541    $config_txt .= $relocation_code;
542  } else {
543    $heavy_txt .= $relocation_code;
544  }
545}
546
547$heavy_txt .= join('', @non_v) . "\n";
548
549# copy config summary format from the myconfig.SH script
550$heavy_txt .= "our \$summary = <<'!END!';\n";
551open(MYCONFIG,"<myconfig.SH") || die "open myconfig.SH failed: $!";
5521 while defined($_ = <MYCONFIG>) && !/^Summary of/;
553do { $heavy_txt .= $_ } until !defined($_ = <MYCONFIG>) || /^\s*$/;
554close(MYCONFIG);
555
556$heavy_txt .= "\n!END!\n" . <<'EOT';
557my $summary_expanded;
558
559sub myconfig {
560    return $summary_expanded if $summary_expanded;
561    ($summary_expanded = $summary) =~ s{\$(\w+)}
562		 {
563			my $c;
564			if ($1 eq 'git_ancestor_line') {
565				if ($Config::Config{git_ancestor}) {
566					$c= "\n  Ancestor: $Config::Config{git_ancestor}";
567				} else {
568					$c= "";
569				}
570			} else {
571                     		$c = $Config::Config{$1};
572			}
573			defined($c) ? $c : 'undef'
574		}ge;
575    $summary_expanded;
576}
577
578local *_ = \my $a;
579$_ = <<'!END!';
580EOT
581
582$heavy_txt .= join('', sort @v_others) . "!END!\n";
583
584# Only need the dynamic byteorder code in Config.pm if 'byteorder' is one of
585# the precached keys
586if ($Common{byteorder}) {
587    $config_txt .= $byteorder_code;
588} else {
589    $heavy_txt .= $byteorder_code;
590}
591
592if (@need_relocation) {
593$heavy_txt .= 'foreach my $what (qw(' . join (' ', @need_relocation) .
594      ")) {\n" . <<'EOT';
595    s/^($what=)(['"])(.*?)\2/$1 . $2 . relocate_inc($3) . $2/me;
596}
597EOT
598# Currently it only makes sense to do the ... relocation on Unix, so there's
599# no need to emulate the "which separator for this platform" logic in perl.c -
600# ':' will always be applicable
601if ($need_relocation{otherlibdirs}) {
602$heavy_txt .= << 'EOT';
603s{^(otherlibdirs=)(['"])(.*?)\2}
604 {$1 . $2 . join ':', map {relocate_inc($_)} split ':', $3 . $2}me;
605EOT
606}
607}
608
609$heavy_txt .= <<'EOT';
610s/(byteorder=)(['"]).*?\2/$1$2$Config::byteorder$2/m;
611
612my $config_sh_len = length $_;
613
614our $Config_SH_expanded = "\n$_" . << 'EOVIRTUAL';
615EOT
616
617foreach my $prefix (qw(ccflags ldflags)) {
618    my $value = fetch_string ({}, $prefix);
619    my $withlargefiles = fetch_string ({}, $prefix . "_uselargefiles");
620    if (defined $withlargefiles) {
621        $value =~ s/\Q$withlargefiles\E\b//;
622        $heavy_txt .= "${prefix}_nolargefiles='$value'\n";
623    }
624}
625
626foreach my $prefix (qw(libs libswanted)) {
627    my $value = fetch_string ({}, $prefix);
628    my $withlf = fetch_string ({}, 'libswanted_uselargefiles');
629    next unless defined $withlf;
630    my @lflibswanted
631       = split(' ', fetch_string ({}, 'libswanted_uselargefiles'));
632    if (@lflibswanted) {
633	my %lflibswanted;
634	@lflibswanted{@lflibswanted} = ();
635	if ($prefix eq 'libs') {
636	    my @libs = grep { /^-l(.+)/ &&
637                            not exists $lflibswanted{$1} }
638		                    split(' ', fetch_string ({}, 'libs'));
639	    $value = join(' ', @libs);
640	} else {
641	    my @libswanted = grep { not exists $lflibswanted{$_} }
642	                          split(' ', fetch_string ({}, 'libswanted'));
643	    $value = join(' ', @libswanted);
644	}
645    }
646    $heavy_txt .= "${prefix}_nolargefiles='$value'\n";
647}
648
649$heavy_txt .= "EOVIRTUAL\n";
650
651$heavy_txt .= <<'ENDOFGIT';
652eval {
653	# do not have hairy conniptions if this isnt available
654	require 'Config_git.pl';
655	$Config_SH_expanded .= $Config::Git_Data;
656	1;
657} or warn "Warning: failed to load Config_git.pl, something strange about this perl...\n";
658ENDOFGIT
659
660$heavy_txt .= $fetch_string;
661
662$config_txt .= <<'ENDOFEND';
663
664sub FETCH {
665    my($self, $key) = @_;
666
667    # check for cached value (which may be undef so we use exists not defined)
668    return exists $self->{$key} ? $self->{$key} : $self->fetch_string($key);
669}
670
671ENDOFEND
672
673$heavy_txt .= <<'ENDOFEND';
674
675my $prevpos = 0;
676
677sub FIRSTKEY {
678    $prevpos = 0;
679    substr($Config_SH_expanded, 1, index($Config_SH_expanded, '=') - 1 );
680}
681
682sub NEXTKEY {
683ENDOFEND
684if ($seen_quotes{'"'}) {
685$heavy_txt .= <<'ENDOFEND';
686    # Find out how the current key's quoted so we can skip to its end.
687    my $quote = substr($Config_SH_expanded,
688		       index($Config_SH_expanded, "=", $prevpos)+1, 1);
689    my $pos = index($Config_SH_expanded, qq($quote\n), $prevpos) + 2;
690ENDOFEND
691} else {
692    # Just ' quotes, so it's much easier.
693$heavy_txt .= <<'ENDOFEND';
694    my $pos = index($Config_SH_expanded, qq('\n), $prevpos) + 2;
695ENDOFEND
696}
697$heavy_txt .= <<'ENDOFEND';
698    my $len = index($Config_SH_expanded, "=", $pos) - $pos;
699    $prevpos = $pos;
700    $len > 0 ? substr($Config_SH_expanded, $pos, $len) : undef;
701}
702
703sub EXISTS {
704    return 1 if exists($_[0]->{$_[1]});
705
706    return(index($Config_SH_expanded, "\n$_[1]='") != -1
707ENDOFEND
708if ($seen_quotes{'"'}) {
709$heavy_txt .= <<'ENDOFEND';
710           or index($Config_SH_expanded, "\n$_[1]=\"") != -1
711ENDOFEND
712}
713$heavy_txt .= <<'ENDOFEND';
714          );
715}
716
717sub STORE  { die "\%Config::Config is read-only\n" }
718*DELETE = *CLEAR = \*STORE; # Typeglob aliasing uses less space
719
720sub config_sh {
721    substr $Config_SH_expanded, 1, $config_sh_len;
722}
723
724sub config_re {
725    my $re = shift;
726    return map { chomp; $_ } grep eval{ /^(?:$re)=/ }, split /^/,
727    $Config_SH_expanded;
728}
729
730sub config_vars {
731    # implements -V:cfgvar option (see perlrun -V:)
732    foreach (@_) {
733	# find optional leading, trailing colons; and query-spec
734	my ($notag,$qry,$lncont) = m/^(:)?(.*?)(:)?$/;	# flags fore and aft,
735	# map colon-flags to print decorations
736	my $prfx = $notag ? '': "$qry=";		# tag-prefix for print
737	my $lnend = $lncont ? ' ' : ";\n";		# line ending for print
738
739	# all config-vars are by definition \w only, any \W means regex
740	if ($qry =~ /\W/) {
741	    my @matches = config_re($qry);
742	    print map "$_$lnend", @matches ? @matches : "$qry: not found"		if !$notag;
743	    print map { s/\w+=//; "$_$lnend" } @matches ? @matches : "$qry: not found"	if  $notag;
744	} else {
745	    my $v = (exists $Config::Config{$qry}) ? $Config::Config{$qry}
746						   : 'UNKNOWN';
747	    $v = 'undef' unless defined $v;
748	    print "${prfx}'${v}'$lnend";
749	}
750    }
751}
752
753# Called by the real AUTOLOAD
754sub launcher {
755    undef &AUTOLOAD;
756    goto \&$Config::AUTOLOAD;
757}
758
7591;
760ENDOFEND
761
762if ($^O eq 'os2') {
763    $config_txt .= <<'ENDOFSET';
764my %preconfig;
765if ($OS2::is_aout) {
766    my ($value, $v) = $Config_SH_expanded =~ m/^used_aout='(.*)'\s*$/m;
767    for (split ' ', $value) {
768        ($v) = $Config_SH_expanded =~ m/^aout_$_='(.*)'\s*$/m;
769        $preconfig{$_} = $v eq 'undef' ? undef : $v;
770    }
771}
772$preconfig{d_fork} = undef unless $OS2::can_fork; # Some funny cases can't
773sub TIEHASH { bless {%preconfig} }
774ENDOFSET
775    # Extract the name of the DLL from the makefile to avoid duplication
776    my ($f) = grep -r, qw(GNUMakefile Makefile);
777    my $dll;
778    if (open my $fh, '<', $f) {
779	while (<$fh>) {
780	    $dll = $1, last if /^PERL_DLL_BASE\s*=\s*(\S*)\s*$/;
781	}
782    }
783    $config_txt .= <<ENDOFSET if $dll;
784\$preconfig{dll_name} = '$dll';
785ENDOFSET
786} else {
787    $config_txt .= <<'ENDOFSET';
788sub TIEHASH {
789    bless $_[1], $_[0];
790}
791ENDOFSET
792}
793
794foreach my $key (keys %Common) {
795    my $value = fetch_string ({}, $key);
796    # Is it safe on the LHS of => ?
797    my $qkey = $key =~ /^[A-Za-z_][A-Za-z0-9_]*$/ ? $key : "'$key'";
798    if (defined $value) {
799	# Quote things for a '' string
800	$value =~ s!\\!\\\\!g;
801	$value =~ s!'!\\'!g;
802	$value = "'$value'";
803	if ($key eq 'otherlibdirs') {
804	    $value = "join (':', map {relocate_inc(\$_)} split (':', $value))";
805	} elsif ($need_relocation{$key}) {
806	    $value = "relocate_inc($value)";
807	}
808    } else {
809	$value = "undef";
810    }
811    $Common{$key} = "$qkey => $value";
812}
813
814if ($Common{byteorder}) {
815    $Common{byteorder} = 'byteorder => $byteorder';
816}
817my $fast_config = join '', map { "    $_,\n" } sort values %Common;
818
819# Sanity check needed to stop an infite loop if Config_heavy.pl fails to define
820# &launcher for some reason (eg it got truncated)
821$config_txt .= sprintf <<'ENDOFTIE', $fast_config;
822
823sub DESTROY { }
824
825sub AUTOLOAD {
826    require 'Config_heavy.pl';
827    goto \&launcher unless $Config::AUTOLOAD =~ /launcher$/;
828    die "&Config::AUTOLOAD failed on $Config::AUTOLOAD";
829}
830
831# tie returns the object, so the value returned to require will be true.
832tie %%Config, 'Config', {
833%s};
834ENDOFTIE
835
836
837open(CONFIG_POD, ">$Config_POD") or die "Can't open $Config_POD: $!";
838print CONFIG_POD <<'ENDOFTAIL';
839=head1 NAME
840
841Config - access Perl configuration information
842
843=head1 SYNOPSIS
844
845    use Config;
846    if ($Config{usethreads}) {
847	print "has thread support\n"
848    }
849
850    use Config qw(myconfig config_sh config_vars config_re);
851
852    print myconfig();
853
854    print config_sh();
855
856    print config_re();
857
858    config_vars(qw(osname archname));
859
860
861=head1 DESCRIPTION
862
863The Config module contains all the information that was available to
864the C<Configure> program at Perl build time (over 900 values).
865
866Shell variables from the F<config.sh> file (written by Configure) are
867stored in the readonly-variable C<%Config>, indexed by their names.
868
869Values stored in config.sh as 'undef' are returned as undefined
870values.  The perl C<exists> function can be used to check if a
871named variable exists.
872
873For a description of the variables, please have a look at the
874Glossary file, as written in the Porting folder, or use the url:
875http://perl5.git.perl.org/perl.git/blob/HEAD:/Porting/Glossary
876
877=over 4
878
879=item myconfig()
880
881Returns a textual summary of the major perl configuration values.
882See also C<-V> in L<perlrun/Command Switches>.
883
884=item config_sh()
885
886Returns the entire perl configuration information in the form of the
887original config.sh shell variable assignment script.
888
889=item config_re($regex)
890
891Like config_sh() but returns, as a list, only the config entries who's
892names match the $regex.
893
894=item config_vars(@names)
895
896Prints to STDOUT the values of the named configuration variable. Each is
897printed on a separate line in the form:
898
899  name='value';
900
901Names which are unknown are output as C<name='UNKNOWN';>.
902See also C<-V:name> in L<perlrun/Command Switches>.
903
904=item bincompat_options()
905
906Returns a list of C pre-processor options used when compiling this F<perl>
907binary, which affect its binary compatibility with extensions.
908C<bincompat_options()> and C<non_bincompat_options()> are shown together in
909the output of C<perl -V> as I<Compile-time options>.
910
911=item non_bincompat_options()
912
913Returns a list of C pre-processor options used when compiling this F<perl>
914binary, which do not affect binary compatibility with extensions.
915
916=item compile_date()
917
918Returns the compile date (as a string), equivalent to what is shown by
919C<perl -V>
920
921=item local_patches()
922
923Returns a list of the names of locally applied patches, equivalent to what
924is shown by C<perl -V>.
925
926=item header_files()
927
928Returns a list of the header files that should be used as dependencies for
929XS code, for this version of Perl on this platform.
930
931=back
932
933=head1 EXAMPLE
934
935Here's a more sophisticated example of using %Config:
936
937    use Config;
938    use strict;
939
940    my %sig_num;
941    my @sig_name;
942    unless($Config{sig_name} && $Config{sig_num}) {
943	die "No sigs?";
944    } else {
945	my @names = split ' ', $Config{sig_name};
946	@sig_num{@names} = split ' ', $Config{sig_num};
947	foreach (@names) {
948	    $sig_name[$sig_num{$_}] ||= $_;
949	}
950    }
951
952    print "signal #17 = $sig_name[17]\n";
953    if ($sig_num{ALRM}) {
954	print "SIGALRM is $sig_num{ALRM}\n";
955    }
956
957=head1 WARNING
958
959Because this information is not stored within the perl executable
960itself it is possible (but unlikely) that the information does not
961relate to the actual perl binary which is being used to access it.
962
963The Config module is installed into the architecture and version
964specific library directory ($Config{installarchlib}) and it checks the
965perl version number when loaded.
966
967The values stored in config.sh may be either single-quoted or
968double-quoted. Double-quoted strings are handy for those cases where you
969need to include escape sequences in the strings. To avoid runtime variable
970interpolation, any C<$> and C<@> characters are replaced by C<\$> and
971C<\@>, respectively. This isn't foolproof, of course, so don't embed C<\$>
972or C<\@> in double-quoted strings unless you're willing to deal with the
973consequences. (The slashes will end up escaped and the C<$> or C<@> will
974trigger variable interpolation)
975
976=head1 GLOSSARY
977
978Most C<Config> variables are determined by the C<Configure> script
979on platforms supported by it (which is most UNIX platforms).  Some
980platforms have custom-made C<Config> variables, and may thus not have
981some of the variables described below, or may have extraneous variables
982specific to that particular port.  See the port specific documentation
983in such cases.
984
985=cut
986
987ENDOFTAIL
988
989if ($Opts{glossary}) {
990  open(GLOS, "<$Glossary") or die "Can't open $Glossary: $!";
991}
992my %seen = ();
993my $text = 0;
994$/ = '';
995
996sub process {
997  if (s/\A(\w*)\s+\(([\w.]+)\):\s*\n(\t?)/=item C<$1>\n\nFrom F<$2>:\n\n/m) {
998    my $c = substr $1, 0, 1;
999    unless ($seen{$c}++) {
1000      print CONFIG_POD <<EOF if $text;
1001=back
1002
1003=cut
1004
1005EOF
1006      print CONFIG_POD <<EOF;
1007=head2 $c
1008
1009=over 4
1010
1011=cut
1012
1013EOF
1014     $text = 1;
1015    }
1016  }
1017  elsif (!$text || !/\A\t/) {
1018    warn "Expected a Configure variable header",
1019      ($text ? " or another paragraph of description" : () );
1020  }
1021  s/n't/n\00t/g;		# leave can't, won't etc untouched
1022  s/^\t\s+(.*)/\n$1/gm;		# Indented lines ===> new paragraph
1023  s/^(?<!\n\n)\t(.*)/$1/gm;	# Not indented lines ===> text
1024  s{([\'\"])(?=[^\'\"\s]*[./][^\'\"\s]*\1)([^\'\"\s]+)\1}(F<$2>)g; # '.o'
1025  s{([\'\"])([^\'\"\s]+)\1}(C<$2>)g; # "date" command
1026  s{\'([A-Za-z_\- *=/]+)\'}(C<$1>)g; # 'ln -s'
1027  s{
1028     (?<! [\w./<\'\"] )		# Only standalone file names
1029     (?! e \. g \. )		# Not e.g.
1030     (?! \. \. \. )		# Not ...
1031     (?! \d )			# Not 5.004
1032     (?! read/ )		# Not read/write
1033     (?! etc\. )		# Not etc.
1034     (?! I/O )			# Not I/O
1035     (
1036	\$ ?			# Allow leading $
1037	[\w./]* [./] [\w./]*	# Require . or / inside
1038     )
1039     (?<! \. (?= [\s)] ) )	# Do not include trailing dot
1040     (?! [\w/] )		# Include all of it
1041   }
1042   (F<$1>)xg;			# /usr/local
1043  s/((?<=\s)~\w*)/F<$1>/g;	# ~name
1044  s/(?<![.<\'\"])\b([A-Z_]{2,})\b(?![\'\"])/C<$1>/g;	# UNISTD
1045  s/(?<![.<\'\"])\b(?!the\b)(\w+)\s+macro\b/C<$1> macro/g; # FILE_cnt macro
1046  s/n[\0]t/n't/g;		# undo can't, won't damage
1047}
1048
1049if ($Opts{glossary}) {
1050    <GLOS>;				# Skip the "DO NOT EDIT"
1051    <GLOS>;				# Skip the preamble
1052  while (<GLOS>) {
1053    process;
1054    print CONFIG_POD;
1055  }
1056}
1057
1058print CONFIG_POD <<'ENDOFTAIL';
1059
1060=back
1061
1062=head1 GIT DATA
1063
1064Information on the git commit from which the current perl binary was compiled
1065can be found in the variable C<$Config::Git_Data>.  The variable is a
1066structured string that looks something like this:
1067
1068  git_commit_id='ea0c2dbd5f5ac6845ecc7ec6696415bf8e27bd52'
1069  git_describe='GitLive-blead-1076-gea0c2db'
1070  git_branch='smartmatch'
1071  git_uncommitted_changes=''
1072  git_commit_id_title='Commit id:'
1073  git_commit_date='2009-05-09 17:47:31 +0200'
1074
1075Its format is not guaranteed not to change over time.
1076
1077=head1 NOTE
1078
1079This module contains a good example of how to use tie to implement a
1080cache and an example of how to make a tied variable readonly to those
1081outside of it.
1082
1083=cut
1084
1085ENDOFTAIL
1086
1087close(GLOS) if $Opts{glossary};
1088close(CONFIG_POD);
1089print "written $Config_POD\n";
1090
1091my $orig_config_txt = "";
1092my $orig_heavy_txt = "";
1093{
1094    local $/;
1095    my $fh;
1096    $orig_config_txt = <$fh> if open $fh, "<", $Config_PM;
1097    $orig_heavy_txt  = <$fh> if open $fh, "<", $Config_heavy;
1098}
1099
1100if ($orig_config_txt ne $config_txt or $orig_heavy_txt ne $heavy_txt) {
1101    open CONFIG, ">", $Config_PM or die "Can't open $Config_PM: $!\n";
1102    open CONFIG_HEAVY, ">", $Config_heavy or die "Can't open $Config_heavy: $!\n";
1103    print CONFIG $config_txt;
1104    print CONFIG_HEAVY $heavy_txt;
1105    close(CONFIG_HEAVY);
1106    close(CONFIG);
1107    print "updated $Config_PM\n";
1108    print "updated $Config_heavy\n";
1109}
1110
1111
1112# Now create Cross.pm if needed
1113if ($Opts{cross}) {
1114  open CROSS, ">lib/Cross.pm" or die "Can not open >lib/Cross.pm: $!";
1115  my $cross = <<'EOS';
1116# typical invocation:
1117#   perl -MCross Makefile.PL
1118#   perl -MCross=wince -V:cc
1119package Cross;
1120
1121sub import {
1122  my ($package,$platform) = @_;
1123  unless (defined $platform) {
1124    # if $platform is not specified, then use last one when
1125    # 'configpm; was invoked with --cross option
1126    $platform = '***replace-marker***';
1127  }
1128  @INC = map {/\blib\b/?(do{local $_=$_;s/\blib\b/xlib\/$platform/;$_},$_):($_)} @INC;
1129  $::Cross::platform = $platform;
1130}
1131
11321;
1133EOS
1134  $cross =~ s/\*\*\*replace-marker\*\*\*/$Opts{cross}/g;
1135  print CROSS $cross;
1136  close CROSS;
1137  print "written lib/Cross.pm\n";
1138  unshift(@INC,"xlib/$Opts{cross}");
1139}
1140
1141# Now do some simple tests on the Config.pm file we have created
1142unshift(@INC,'lib');
1143unshift(@INC,'xlib/symbian') if $Opts{cross};
1144require $Config_PM;
1145require $Config_heavy;
1146import Config;
1147
1148die "$0: $Config_PM not valid"
1149	unless $Config{'PERL_CONFIG_SH'} eq 'true';
1150
1151die "$0: error processing $Config_PM"
1152	if defined($Config{'an impossible name'})
1153	or $Config{'PERL_CONFIG_SH'} ne 'true' # test cache
1154	;
1155
1156die "$0: error processing $Config_PM"
1157	if eval '$Config{"cc"} = 1'
1158	or eval 'delete $Config{"cc"}'
1159	;
1160
1161
1162exit 0;
1163# Popularity of various entries in %Config, based on a large build and test
1164# run of code in the Fotango build system:
1165__DATA__
1166path_sep:	8490
1167d_readlink:	7101
1168d_symlink:	7101
1169archlibexp:	4318
1170sitearchexp:	4305
1171sitelibexp:	4305
1172privlibexp:	4163
1173ldlibpthname:	4041
1174libpth:	2134
1175archname:	1591
1176exe_ext:	1256
1177scriptdir:	1155
1178version:	1116
1179useithreads:	1002
1180osvers:	982
1181osname:	851
1182inc_version_list:	783
1183dont_use_nlink:	779
1184intsize:	759
1185usevendorprefix:	642
1186dlsrc:	624
1187cc:	541
1188lib_ext:	520
1189so:	512
1190ld:	501
1191ccdlflags:	500
1192ldflags:	495
1193obj_ext:	495
1194cccdlflags:	493
1195lddlflags:	493
1196ar:	492
1197dlext:	492
1198libc:	492
1199ranlib:	492
1200full_ar:	491
1201vendorarchexp:	491
1202vendorlibexp:	491
1203installman1dir:	489
1204installman3dir:	489
1205installsitebin:	489
1206installsiteman1dir:	489
1207installsiteman3dir:	489
1208installvendorman1dir:	489
1209installvendorman3dir:	489
1210d_flexfnam:	474
1211eunicefix:	360
1212d_link:	347
1213installsitearch:	344
1214installscript:	341
1215installprivlib:	337
1216binexp:	336
1217installarchlib:	336
1218installprefixexp:	336
1219installsitelib:	336
1220installstyle:	336
1221installvendorarch:	336
1222installvendorbin:	336
1223installvendorlib:	336
1224man1ext:	336
1225man3ext:	336
1226sh:	336
1227siteprefixexp:	336
1228installbin:	335
1229usedl:	332
1230ccflags:	285
1231startperl:	232
1232optimize:	231
1233usemymalloc:	229
1234cpprun:	228
1235sharpbang:	228
1236perllibs:	225
1237usesfio:	224
1238usethreads:	220
1239perlpath:	218
1240extensions:	217
1241usesocks:	208
1242shellflags:	198
1243make:	191
1244d_pwage:	189
1245d_pwchange:	189
1246d_pwclass:	189
1247d_pwcomment:	189
1248d_pwexpire:	189
1249d_pwgecos:	189
1250d_pwpasswd:	189
1251d_pwquota:	189
1252gccversion:	189
1253libs:	186
1254useshrplib:	186
1255cppflags:	185
1256ptrsize:	185
1257shrpenv:	185
1258static_ext:	185
1259use5005threads:	185
1260uselargefiles:	185
1261alignbytes:	184
1262byteorder:	184
1263ccversion:	184
1264config_args:	184
1265cppminus:	184
1266