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