xref: /openbsd/gnu/usr.bin/perl/configpm (revision cbfb5651)
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# allowed opts as well as specifies default and initial values
91my %Allowed_Opts = (
92    'glossary' => 1,  # --no-glossary  - no glossary file inclusion,
93                      #                  for compactness
94    'chdir'    => '', # --chdir=dir    - change directory before writing files
95);
96
97sub opts {
98    # user specified options
99    my %given_opts = (
100        # --opt=smth
101        (map {/^--([\-_\w]+)=(.*)$/} @ARGV),
102        # --opt --no-opt --noopt
103        (map {/^no-?(.*)$/i?($1=>0):($_=>1)} map {/^--([\-_\w]+)$/} @ARGV),
104    );
105
106    my %opts = (%Allowed_Opts, %given_opts);
107
108    for my $opt (grep {!exists $Allowed_Opts{$_}} keys %given_opts) {
109        warn "option '$opt' is not recognized";
110	usage;
111    }
112    @ARGV = grep {!/^--/} @ARGV;
113
114    return %opts;
115}
116
117
118my %Opts = opts();
119
120if ($Opts{chdir}) {
121    chdir $Opts{chdir} or die "$0: could not chdir $Opts{chdir}: $!"
122}
123
124my ($Config_SH, $Config_PM, $Config_heavy, $Config_POD);
125my $Glossary = 'Porting/Glossary';
126
127$Config_PM = "lib/Config.pm";
128$Config_POD = "lib/Config.pod";
129$Config_SH = "config.sh";
130
131($Config_heavy = $Config_PM) =~ s/\.pm$/_heavy.pl/;
132die "Can't automatically determine name for Config_heavy.pl from '$Config_PM'"
133  if $Config_heavy eq $Config_PM;
134
135my $config_txt;
136my $heavy_txt;
137
138my $export_funcs = <<'EOT';
139my %Export_Cache = (myconfig => 1, config_sh => 1, config_vars => 1,
140		    config_re => 1, compile_date => 1, local_patches => 1,
141		    bincompat_options => 1, non_bincompat_options => 1,
142		    header_files => 1);
143EOT
144
145my %export_ok = eval $export_funcs or die;
146
147$config_txt .= sprintf << 'EOT', $], $export_funcs;
148# This file was created by configpm when Perl was built. Any changes
149# made to this file will be lost the next time perl is built.
150
151# for a description of the variables, please have a look at the
152# Glossary file, as written in the Porting folder, or use the url:
153# http://perl5.git.perl.org/perl.git/blob/HEAD:/Porting/Glossary
154
155package Config;
156use strict;
157use warnings;
158use vars '%%Config', '$VERSION';
159
160$VERSION = "%s";
161
162# Skip @Config::EXPORT because it only contains %%Config, which we special
163# case below as it's not a function. @Config::EXPORT won't change in the
164# lifetime of Perl 5.
165%s
166@Config::EXPORT = qw(%%Config);
167@Config::EXPORT_OK = keys %%Export_Cache;
168
169# Need to stub all the functions to make code such as print Config::config_sh
170# keep working
171
172EOT
173
174$config_txt .= "sub $_;\n" foreach sort keys %export_ok;
175
176my $myver = sprintf "%vd", $^V;
177
178$config_txt .= sprintf <<'ENDOFBEG', ($myver) x 3;
179
180# Define our own import method to avoid pulling in the full Exporter:
181sub import {
182    shift;
183    @_ = @Config::EXPORT unless @_;
184
185    my @funcs = grep $_ ne '%%Config', @_;
186    my $export_Config = @funcs < @_ ? 1 : 0;
187
188    no strict 'refs';
189    my $callpkg = caller(0);
190    foreach my $func (@funcs) {
191	die qq{"$func" is not exported by the Config module\n}
192	    unless $Export_Cache{$func};
193	*{$callpkg.'::'.$func} = \&{$func};
194    }
195
196    *{"$callpkg\::Config"} = \%%Config if $export_Config;
197    return;
198}
199
200die "$0: Perl lib version (%s) doesn't match executable '$^X' version ($])"
201    unless $^V;
202
203$^V eq %s
204    or die sprintf "%%s: Perl lib version (%s) doesn't match executable '$^X' version (%%vd)", $0, $^V;
205
206ENDOFBEG
207
208
209my @non_v    = ();
210my @v_others = ();
211my $in_v     = 0;
212my %Data     = ();
213my $quote;
214
215
216my %seen_quotes;
217{
218  my ($name, $val);
219  open(CONFIG_SH, $Config_SH) || die "Can't open $Config_SH: $!";
220  while (<CONFIG_SH>) {
221    next if m:^#!/bin/sh:;
222
223    # Catch PERL_CONFIG_SH=true and PERL_VERSION=n line from Configure.
224    s/^(\w+)=(true|\d+)\s*$/$1='$2'\n/ or m/^(\w+)='(.*)'$/;
225    my($k, $v) = ($1, $2);
226
227    # grandfather PATCHLEVEL and SUBVERSION and CONFIG
228    if ($k) {
229	if ($k eq 'PERL_VERSION') {
230	    push @v_others, "PATCHLEVEL='$v'\n";
231	}
232	elsif ($k eq 'PERL_SUBVERSION') {
233	    push @v_others, "SUBVERSION='$v'\n";
234	}
235	elsif ($k eq 'PERL_CONFIG_SH') {
236	    push @v_others, "CONFIG='$v'\n";
237	}
238    }
239
240    # We can delimit things in config.sh with either ' or ".
241    unless ($in_v or m/^(\w+)=(['"])(.*\n)/){
242	push(@non_v, "#$_"); # not a name='value' line
243	next;
244    }
245    if ($in_v) {
246        $val .= $_;
247    }
248    else {
249	$quote = $2;
250        ($name,$val) = ($1,$3);
251    }
252    $in_v = $val !~ /$quote\n/;
253    next if $in_v;
254
255    s,/,::,g if $Extensions{$name};
256
257    $val =~ s/$quote\n?\z//;
258
259    my $line = "$name=$quote$val$quote\n";
260    push(@v_others, $line);
261    $seen_quotes{$quote}++;
262  }
263  close CONFIG_SH;
264}
265
266# This is somewhat grim, but I want the code for parsing config.sh here and
267# now so that I can expand $Config{ivsize} and $Config{ivtype}
268
269my $fetch_string = <<'EOT';
270
271# Search for it in the big string
272sub fetch_string {
273    my($self, $key) = @_;
274
275EOT
276
277if ($seen_quotes{'"'}) {
278    # We need the full ' and " code
279
280$fetch_string .= <<'EOT';
281    return undef unless my ($quote_type, $value) = $Config_SH_expanded =~ /\n$key=(['"])(.*?)\1\n/s;
282
283    # If we had a double-quote, we'd better eval it so escape
284    # sequences and such can be interpolated. Since the incoming
285    # value is supposed to follow shell rules and not perl rules,
286    # we escape any perl variable markers
287
288    # Historically, since " 'support' was added in change 1409, the
289    # interpolation was done before the undef. Stick to this arguably buggy
290    # behaviour as we're refactoring.
291    if ($quote_type eq '"') {
292	$value =~ s/\$/\\\$/g;
293	$value =~ s/\@/\\\@/g;
294	eval "\$value = \"$value\"";
295    }
296
297    # So we can say "if $Config{'foo'}".
298    $self->{$key} = $value eq 'undef' ? undef : $value; # cache it
299}
300EOT
301
302} else {
303    # We only have ' delimited.
304
305$fetch_string .= <<'EOT';
306    return undef unless $Config_SH_expanded =~ /\n$key=\'(.*?)\'\n/s;
307    # So we can say "if $Config{'foo'}".
308    $self->{$key} = $1 eq 'undef' ? undef : $1;
309}
310EOT
311
312}
313
314eval $fetch_string;
315die if $@;
316
317# Calculation for the keys for byteorder
318# This is somewhat grim, but I need to run fetch_string here.
319our $Config_SH_expanded = join "\n", '', @v_others;
320
321my $t = fetch_string ({}, 'ivtype');
322my $s = fetch_string ({}, 'ivsize');
323
324# byteorder does exist on its own but we overlay a virtual
325# dynamically recomputed value.
326
327# However, ivtype and ivsize will not vary for sane fat binaries
328
329my $f = $t eq 'long' ? 'L!' : $s == 8 ? 'Q': 'I';
330
331my $byteorder_code;
332if ($s == 4 || $s == 8) {
333    my $list = join ',', reverse(1..$s-1);
334    my $format = 'a'x$s;
335    $byteorder_code = <<"EOT";
336
337my \$i = ord($s);
338foreach my \$c ($list) { \$i <<= 8; \$i |= ord(\$c); }
339our \$byteorder = join('', unpack('$format', pack('$f', \$i)));
340EOT
341} else {
342    $byteorder_code = "our \$byteorder = '?'x$s;\n";
343}
344
345my @need_relocation;
346
347if (fetch_string({},'userelocatableinc')) {
348    foreach my $what (qw(prefixexp
349
350			 archlibexp
351			 html1direxp
352			 html3direxp
353			 man1direxp
354			 man3direxp
355			 privlibexp
356			 scriptdirexp
357			 sitearchexp
358			 sitebinexp
359			 sitehtml1direxp
360			 sitehtml3direxp
361			 sitelibexp
362			 siteman1direxp
363			 siteman3direxp
364			 sitescriptexp
365			 vendorarchexp
366			 vendorbinexp
367			 vendorhtml1direxp
368			 vendorhtml3direxp
369			 vendorlibexp
370			 vendorman1direxp
371			 vendorman3direxp
372			 vendorscriptexp
373
374			 siteprefixexp
375			 sitelib_stem
376			 vendorlib_stem
377
378			 installarchlib
379			 installhtml1dir
380			 installhtml3dir
381			 installman1dir
382			 installman3dir
383			 installprefix
384			 installprefixexp
385			 installprivlib
386			 installscript
387			 installsitearch
388			 installsitebin
389			 installsitehtml1dir
390			 installsitehtml3dir
391			 installsitelib
392			 installsiteman1dir
393			 installsiteman3dir
394			 installsitescript
395			 installvendorarch
396			 installvendorbin
397			 installvendorhtml1dir
398			 installvendorhtml3dir
399			 installvendorlib
400			 installvendorman1dir
401			 installvendorman3dir
402			 installvendorscript
403			 )) {
404	push @need_relocation, $what if fetch_string({}, $what) =~ m!^\.\.\./!;
405    }
406}
407
408my %need_relocation;
409@need_relocation{@need_relocation} = @need_relocation;
410
411# This can have .../ anywhere:
412if (fetch_string({}, 'otherlibdirs') =~ m!\.\.\./!) {
413    $need_relocation{otherlibdirs} = 'otherlibdirs';
414}
415
416my $relocation_code = <<'EOT';
417
418sub relocate_inc {
419  my $libdir = shift;
420  return $libdir unless $libdir =~ s!^\.\.\./!!;
421  my $prefix = $^X;
422  if ($prefix =~ s!/[^/]*$!!) {
423    while ($libdir =~ m!^\.\./!) {
424      # Loop while $libdir starts "../" and $prefix still has a trailing
425      # directory
426      last unless $prefix =~ s!/([^/]+)$!!;
427      # but bail out if the directory we picked off the end of $prefix is .
428      # or ..
429      if ($1 eq '.' or $1 eq '..') {
430	# Undo! This should be rare, hence code it this way rather than a
431	# check each time before the s!!! above.
432	$prefix = "$prefix/$1";
433	last;
434      }
435      # Remove that leading ../ and loop again
436      substr ($libdir, 0, 3, '');
437    }
438    $libdir = "$prefix/$libdir";
439  }
440  $libdir;
441}
442EOT
443
444my $osname = fetch_string({}, 'osname');
445my $from = $osname eq 'VMS' ? 'PERLSHR image' : 'binary (from libperl)';
446my $env_cygwin = $osname eq 'cygwin'
447    ? 'push @env, "CYGWIN=\"$ENV{CYGWIN}\"" if $ENV{CYGWIN};' . "\n" : "";
448
449$heavy_txt .= sprintf <<'ENDOFBEG', $osname, $osname, $from, $osname, $env_cygwin;
450# This file was created by configpm when Perl was built. Any changes
451# made to this file will be lost the next time perl is built.
452
453package Config;
454use strict;
455use warnings;
456use vars '%%Config';
457
458sub bincompat_options {
459    return split ' ', (Internals::V())[0];
460}
461
462sub non_bincompat_options {
463    return split ' ', (Internals::V())[1];
464}
465
466sub compile_date {
467    return (Internals::V())[2]
468}
469
470sub local_patches {
471    my (undef, undef, undef, @patches) = Internals::V();
472    return @patches;
473}
474
475sub _V {
476    die "Perl lib was built for '%s' but is being run on '$^O'"
477        unless "%s" eq $^O;
478
479    my ($bincompat, $non_bincompat, $date, @patches) = Internals::V();
480
481    my $opts = join ' ', sort split ' ', "$bincompat $non_bincompat";
482
483    # wrap at 76 columns.
484
485    $opts =~ s/(?=.{53})(.{1,53}) /$1\n                        /mg;
486
487    print Config::myconfig();
488    print "\nCharacteristics of this %s: \n";
489
490    print "  Compile-time options: $opts\n";
491
492    if (@patches) {
493        print "  Locally applied patches:\n";
494        print "\t$_\n" foreach @patches;
495    }
496
497    print "  Built under %s\n";
498
499    print "  $date\n" if defined $date;
500
501    my @env = map { "$_=\"$ENV{$_}\"" } sort grep {/^PERL/} keys %%ENV;
502%s
503    if (@env) {
504        print "  \%%ENV:\n";
505        print "    $_\n" foreach @env;
506    }
507    print "  \@INC:\n";
508    print "    $_\n" foreach @INC;
509}
510
511sub header_files {
512ENDOFBEG
513
514$heavy_txt .= $header_files . "\n}\n\n";
515
516if (%need_relocation) {
517  my $relocations_in_common;
518  # otherlibdirs only features in the hash
519  foreach (keys %need_relocation) {
520    $relocations_in_common++ if $Common{$_};
521  }
522  if ($relocations_in_common) {
523    $config_txt .= $relocation_code;
524  } else {
525    $heavy_txt .= $relocation_code;
526  }
527}
528
529$heavy_txt .= join('', @non_v) . "\n";
530
531# copy config summary format from the myconfig.SH script
532$heavy_txt .= "our \$summary = <<'!END!';\n";
533open(MYCONFIG,"<myconfig.SH") || die "open myconfig.SH failed: $!";
5341 while defined($_ = <MYCONFIG>) && !/^Summary of/;
535do { $heavy_txt .= $_ } until !defined($_ = <MYCONFIG>) || /^\s*$/;
536close(MYCONFIG);
537
538$heavy_txt .= "\n!END!\n" . <<'EOT';
539my $summary_expanded;
540
541sub myconfig {
542    return $summary_expanded if $summary_expanded;
543    ($summary_expanded = $summary) =~ s{\$(\w+)}
544		 {
545			my $c;
546			if ($1 eq 'git_ancestor_line') {
547				if ($Config::Config{git_ancestor}) {
548					$c= "\n  Ancestor: $Config::Config{git_ancestor}";
549				} else {
550					$c= "";
551				}
552			} else {
553                     		$c = $Config::Config{$1};
554			}
555			defined($c) ? $c : 'undef'
556		}ge;
557    $summary_expanded;
558}
559
560local *_ = \my $a;
561$_ = <<'!END!';
562EOT
563
564$heavy_txt .= join('', sort @v_others) . "!END!\n";
565
566# Only need the dynamic byteorder code in Config.pm if 'byteorder' is one of
567# the precached keys
568if ($Common{byteorder}) {
569    $config_txt .= $byteorder_code;
570} else {
571    $heavy_txt .= $byteorder_code;
572}
573
574if (@need_relocation) {
575$heavy_txt .= 'foreach my $what (qw(' . join (' ', @need_relocation) .
576      ")) {\n" . <<'EOT';
577    s/^($what=)(['"])(.*?)\2/$1 . $2 . relocate_inc($3) . $2/me;
578}
579EOT
580# Currently it only makes sense to do the ... relocation on Unix, so there's
581# no need to emulate the "which separator for this platform" logic in perl.c -
582# ':' will always be applicable
583if ($need_relocation{otherlibdirs}) {
584$heavy_txt .= << 'EOT';
585s{^(otherlibdirs=)(['"])(.*?)\2}
586 {$1 . $2 . join ':', map {relocate_inc($_)} split ':', $3 . $2}me;
587EOT
588}
589}
590
591$heavy_txt .= <<'EOT';
592s/(byteorder=)(['"]).*?\2/$1$2$Config::byteorder$2/m;
593
594my $config_sh_len = length $_;
595
596our $Config_SH_expanded = "\n$_" . << 'EOVIRTUAL';
597EOT
598
599foreach my $prefix (qw(ccflags ldflags)) {
600    my $value = fetch_string ({}, $prefix);
601    my $withlargefiles = fetch_string ({}, $prefix . "_uselargefiles");
602    if (defined $withlargefiles) {
603        $value =~ s/\Q$withlargefiles\E\b//;
604        $heavy_txt .= "${prefix}_nolargefiles='$value'\n";
605    }
606}
607
608foreach my $prefix (qw(libs libswanted)) {
609    my $value = fetch_string ({}, $prefix);
610    my $withlf = fetch_string ({}, 'libswanted_uselargefiles');
611    next unless defined $withlf;
612    my @lflibswanted
613       = split(' ', fetch_string ({}, 'libswanted_uselargefiles'));
614    if (@lflibswanted) {
615	my %lflibswanted;
616	@lflibswanted{@lflibswanted} = ();
617	if ($prefix eq 'libs') {
618	    my @libs = grep { /^-l(.+)/ &&
619                            not exists $lflibswanted{$1} }
620		                    split(' ', fetch_string ({}, 'libs'));
621	    $value = join(' ', @libs);
622	} else {
623	    my @libswanted = grep { not exists $lflibswanted{$_} }
624	                          split(' ', fetch_string ({}, 'libswanted'));
625	    $value = join(' ', @libswanted);
626	}
627    }
628    $heavy_txt .= "${prefix}_nolargefiles='$value'\n";
629}
630
631if (open(my $fh, "cflags")) {
632    my $ccwarnflags;
633    my $ccstdflags;
634    while (<$fh>) {
635        if (/^warn="(.+)"$/) {
636            $ccwarnflags = $1;
637        } elsif (/^stdflags="(.+)"$/) {
638            $ccstdflags = $1;
639        }
640    }
641    if (defined $ccwarnflags) {
642      $heavy_txt .= "ccwarnflags='$ccwarnflags'\n";
643    }
644    if (defined $ccstdflags) {
645      $heavy_txt .= "ccstdflags='$ccstdflags'\n";
646    }
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 infinite loop if Config_heavy.pl fails to
820# define &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$/ = '';
995my $errors= 0;
996
997sub process {
998  if (s/\A(\w*)\s+\(([\w.]+)\):\s*\n(\t?)/=item C<$1>\n\nFrom F<$2>:\n\n/m) {
999    my $c = substr $1, 0, 1;
1000    unless ($seen{$c}++) {
1001      print CONFIG_POD <<EOF if $text;
1002=back
1003
1004=cut
1005
1006EOF
1007      print CONFIG_POD <<EOF;
1008=head2 $c
1009
1010=over 4
1011
1012=cut
1013
1014EOF
1015     $text = 1;
1016    }
1017  }
1018  elsif (!$text || !/\A\t/) {
1019    warn "Expected a Configure variable header",
1020      ($text ? " or another paragraph of description" : () ),
1021      ", instead we got:\n$_";
1022    $errors++;
1023  }
1024  s/n't/n\00t/g;		# leave can't, won't etc untouched
1025  s/^\t\s+(.*)/\n$1/gm;		# Indented lines ===> new paragraph
1026  s/^(?<!\n\n)\t(.*)/$1/gm;	# Not indented lines ===> text
1027  s{([\'\"])(?=[^\'\"\s]*[./][^\'\"\s]*\1)([^\'\"\s]+)\1}(F<$2>)g; # '.o'
1028  s{([\'\"])([^\'\"\s]+)\1}(C<$2>)g; # "date" command
1029  s{\'([A-Za-z_\- *=/]+)\'}(C<$1>)g; # 'ln -s'
1030  s{
1031     (?<! [\w./<\'\"\$] )		# Only standalone file names
1032     (?! e \. g \. )		# Not e.g.
1033     (?! \. \. \. )		# Not ...
1034     (?! \d )			# Not 5.004
1035     (?! read/ )		# Not read/write
1036     (?! etc\. )		# Not etc.
1037     (?! I/O )			# Not I/O
1038     (
1039	\$ ?			# Allow leading $
1040	[\w./]* [./] [\w./]*	# Require . or / inside
1041     )
1042     (?<! \. (?= [\s)] ) )	# Do not include trailing dot
1043     (?! [\w/] )		# Include all of it
1044   }
1045   (F<$1>)xg;			# /usr/local
1046  s/((?<=\s)~\w*)/F<$1>/g;	# ~name
1047  s/(?<![.<\'\"])\b([A-Z_]{2,})\b(?![\'\"])/C<$1>/g;	# UNISTD
1048  s/(?<![.<\'\"])\b(?!the\b)(\w+)\s+macro\b/C<$1> macro/g; # FILE_cnt macro
1049  s/n[\0]t/n't/g;		# undo can't, won't damage
1050}
1051
1052if ($Opts{glossary}) {
1053    <GLOS>;				# Skip the "DO NOT EDIT"
1054    <GLOS>;				# Skip the preamble
1055  while (<GLOS>) {
1056    process;
1057    print CONFIG_POD;
1058  }
1059  if ($errors) {
1060    die "Errors encountered while processing $Glossary. ",
1061        "Header lines are expected to be of the form:\n",
1062        "NAME (CLASS):\n",
1063        "Maybe there is a malformed header?\n",
1064    ;
1065  }
1066}
1067
1068print CONFIG_POD <<'ENDOFTAIL';
1069
1070=back
1071
1072=head1 GIT DATA
1073
1074Information on the git commit from which the current perl binary was compiled
1075can be found in the variable C<$Config::Git_Data>.  The variable is a
1076structured string that looks something like this:
1077
1078  git_commit_id='ea0c2dbd5f5ac6845ecc7ec6696415bf8e27bd52'
1079  git_describe='GitLive-blead-1076-gea0c2db'
1080  git_branch='smartmatch'
1081  git_uncommitted_changes=''
1082  git_commit_id_title='Commit id:'
1083  git_commit_date='2009-05-09 17:47:31 +0200'
1084
1085Its format is not guaranteed not to change over time.
1086
1087=head1 NOTE
1088
1089This module contains a good example of how to use tie to implement a
1090cache and an example of how to make a tied variable readonly to those
1091outside of it.
1092
1093=cut
1094
1095ENDOFTAIL
1096
1097close(GLOS) if $Opts{glossary};
1098close(CONFIG_POD);
1099print "written $Config_POD\n";
1100
1101my $orig_config_txt = "";
1102my $orig_heavy_txt = "";
1103{
1104    local $/;
1105    my $fh;
1106    $orig_config_txt = <$fh> if open $fh, "<", $Config_PM;
1107    $orig_heavy_txt  = <$fh> if open $fh, "<", $Config_heavy;
1108}
1109
1110if ($orig_config_txt ne $config_txt or $orig_heavy_txt ne $heavy_txt) {
1111    # During the build don't look in /usr/local for libs or includes
1112    # but after, we want to let modules look there.
1113    my $install_heavy_txt = $heavy_txt;
1114    $install_heavy_txt =~ s,^(ccflags|cppflags)[^=]*='[^']+,$& -I/usr/local/include,gm;
1115    $install_heavy_txt =~ s,^(ldflags|lddlflags)[^=]*='[^']+,$& -L/usr/local/lib,gm;
1116
1117    open INSTALL_CONFIG_HEAVY, ">", "$Config_heavy.install"
1118         or die "Can't open install $Config_heavy: $!\n";
1119    print INSTALL_CONFIG_HEAVY $install_heavy_txt;
1120    close INSTALL_CONFIG_HEAVY;
1121    print "updated install $Config_heavy\n";
1122
1123    open CONFIG, ">", $Config_PM or die "Can't open $Config_PM: $!\n";
1124    open CONFIG_HEAVY, ">", $Config_heavy or die "Can't open $Config_heavy: $!\n";
1125    print CONFIG $config_txt;
1126    print CONFIG_HEAVY $heavy_txt;
1127    close(CONFIG_HEAVY);
1128    close(CONFIG);
1129    print "updated $Config_PM\n";
1130    print "updated $Config_heavy\n";
1131}
1132
1133# Now do some simple tests on the Config.pm file we have created
1134unshift(@INC,'lib');
1135require $Config_PM;
1136require $Config_heavy;
1137import Config;
1138
1139die "$0: $Config_PM not valid"
1140	unless $Config{'PERL_CONFIG_SH'} eq 'true';
1141
1142die "$0: error processing $Config_PM"
1143	if defined($Config{'an impossible name'})
1144	or $Config{'PERL_CONFIG_SH'} ne 'true' # test cache
1145	;
1146
1147die "$0: error processing $Config_PM"
1148	if eval '$Config{"cc"} = 1'
1149	or eval 'delete $Config{"cc"}'
1150	;
1151
1152
1153exit 0;
1154# Popularity of various entries in %Config, based on a large build and test
1155# run of code in the Fotango build system:
1156__DATA__
1157path_sep:	8490
1158d_readlink:	7101
1159d_symlink:	7101
1160archlibexp:	4318
1161sitearchexp:	4305
1162sitelibexp:	4305
1163privlibexp:	4163
1164ldlibpthname:	4041
1165libpth:	2134
1166archname:	1591
1167exe_ext:	1256
1168scriptdir:	1155
1169version:	1116
1170useithreads:	1002
1171osvers:	982
1172osname:	851
1173inc_version_list:	783
1174dont_use_nlink:	779
1175intsize:	759
1176usevendorprefix:	642
1177dlsrc:	624
1178cc:	541
1179lib_ext:	520
1180so:	512
1181ld:	501
1182ccdlflags:	500
1183ldflags:	495
1184obj_ext:	495
1185cccdlflags:	493
1186lddlflags:	493
1187ar:	492
1188dlext:	492
1189libc:	492
1190ranlib:	492
1191full_ar:	491
1192vendorarchexp:	491
1193vendorlibexp:	491
1194installman1dir:	489
1195installman3dir:	489
1196installsitebin:	489
1197installsiteman1dir:	489
1198installsiteman3dir:	489
1199installvendorman1dir:	489
1200installvendorman3dir:	489
1201d_flexfnam:	474
1202eunicefix:	360
1203d_link:	347
1204installsitearch:	344
1205installscript:	341
1206installprivlib:	337
1207binexp:	336
1208installarchlib:	336
1209installprefixexp:	336
1210installsitelib:	336
1211installstyle:	336
1212installvendorarch:	336
1213installvendorbin:	336
1214installvendorlib:	336
1215man1ext:	336
1216man3ext:	336
1217sh:	336
1218siteprefixexp:	336
1219installbin:	335
1220usedl:	332
1221ccflags:	285
1222startperl:	232
1223optimize:	231
1224usemymalloc:	229
1225cpprun:	228
1226sharpbang:	228
1227perllibs:	225
1228usesfio:	224
1229usethreads:	220
1230perlpath:	218
1231extensions:	217
1232usesocks:	208
1233shellflags:	198
1234make:	191
1235d_pwage:	189
1236d_pwchange:	189
1237d_pwclass:	189
1238d_pwcomment:	189
1239d_pwexpire:	189
1240d_pwgecos:	189
1241d_pwpasswd:	189
1242d_pwquota:	189
1243gccversion:	189
1244libs:	186
1245useshrplib:	186
1246cppflags:	185
1247ptrsize:	185
1248shrpenv:	185
1249static_ext:	185
1250use5005threads:	185
1251uselargefiles:	185
1252alignbytes:	184
1253byteorder:	184
1254ccversion:	184
1255config_args:	184
1256cppminus:	184
1257