Start anew
[git/jnareb-git.git] / mingw / lib / tcl8.4 / init.tcl
blob810564226b4c2c0e7d021b77a21aafd007c43f81
1 # init.tcl --
3 # Default system startup file for Tcl-based applications. Defines
4 # "unknown" procedure and auto-load facilities.
6 # RCS: @(#) $Id: init.tcl,v 1.55.2.6 2005/07/22 21:59:40 dgp Exp $
8 # Copyright (c) 1991-1993 The Regents of the University of California.
9 # Copyright (c) 1994-1996 Sun Microsystems, Inc.
10 # Copyright (c) 1998-1999 Scriptics Corporation.
12 # See the file "license.terms" for information on usage and redistribution
13 # of this file, and for a DISCLAIMER OF ALL WARRANTIES.
16 if {[info commands package] == ""} {
17 error "version mismatch: library\nscripts expect Tcl version 7.5b1 or later but the loaded version is\nonly [info patchlevel]"
19 package require -exact Tcl 8.4
21 # Compute the auto path to use in this interpreter.
22 # The values on the path come from several locations:
24 # The environment variable TCLLIBPATH
26 # tcl_library, which is the directory containing this init.tcl script.
27 # tclInitScript.h searches around for the directory containing this
28 # init.tcl and defines tcl_library to that location before sourcing it.
30 # The parent directory of tcl_library. Adding the parent
31 # means that packages in peer directories will be found automatically.
33 # Also add the directory ../lib relative to the directory where the
34 # executable is located. This is meant to find binary packages for the
35 # same architecture as the current executable.
37 # tcl_pkgPath, which is set by the platform-specific initialization routines
38 # On UNIX it is compiled in
39 # On Windows, it is not used
40 # On Macintosh it is "Tool Command Language" in the Extensions folder
42 if {![info exists auto_path]} {
43 if {[info exists env(TCLLIBPATH)]} {
44 set auto_path $env(TCLLIBPATH)
45 } else {
46 set auto_path ""
49 namespace eval tcl {
50 variable Dir
51 if {[info library] ne ""} {
52 foreach Dir [list [info library] [file dirname [info library]]] {
53 if {[lsearch -exact $::auto_path $Dir] < 0} {
54 lappend ::auto_path $Dir
58 set Dir [file join [file dirname [file dirname \
59 [info nameofexecutable]]] lib]
60 if {[lsearch -exact $::auto_path $Dir] < 0} {
61 lappend ::auto_path $Dir
63 if {[info exists ::tcl_pkgPath]} {
64 foreach Dir $::tcl_pkgPath {
65 if {[lsearch -exact $::auto_path $Dir] < 0} {
66 lappend ::auto_path $Dir
72 # Windows specific end of initialization
74 if {(![interp issafe]) && $tcl_platform(platform) eq "windows"} {
75 namespace eval tcl {
76 proc EnvTraceProc {lo n1 n2 op} {
77 set x $::env($n2)
78 set ::env($lo) $x
79 set ::env([string toupper $lo]) $x
81 proc InitWinEnv {} {
82 global env tcl_platform
83 foreach p [array names env] {
84 set u [string toupper $p]
85 if {$u ne $p} {
86 switch -- $u {
87 COMSPEC -
88 PATH {
89 if {![info exists env($u)]} {
90 set env($u) $env($p)
92 trace add variable env($p) write \
93 [namespace code [list EnvTraceProc $p]]
94 trace add variable env($u) write \
95 [namespace code [list EnvTraceProc $p]]
100 if {![info exists env(COMSPEC)]} {
101 if {$tcl_platform(os) eq "Windows NT"} {
102 set env(COMSPEC) cmd.exe
103 } else {
104 set env(COMSPEC) command.com
108 InitWinEnv
112 # Setup the unknown package handler
114 package unknown tclPkgUnknown
116 if {![interp issafe]} {
117 # setup platform specific unknown package handlers
118 if {$::tcl_platform(platform) eq "unix"
119 && $::tcl_platform(os) eq "Darwin"} {
120 package unknown [list tcl::MacOSXPkgUnknown [package unknown]]
122 if {$::tcl_platform(platform) eq "macintosh"} {
123 package unknown [list tcl::MacPkgUnknown [package unknown]]
127 # Conditionalize for presence of exec.
129 if {[namespace which -command exec] eq ""} {
131 # Some machines, such as the Macintosh, do not have exec. Also, on all
132 # platforms, safe interpreters do not have exec.
134 set auto_noexec 1
136 set errorCode ""
137 set errorInfo ""
139 # Define a log command (which can be overwitten to log errors
140 # differently, specially when stderr is not available)
142 if {[namespace which -command tclLog] eq ""} {
143 proc tclLog {string} {
144 catch {puts stderr $string}
148 # unknown --
149 # This procedure is called when a Tcl command is invoked that doesn't
150 # exist in the interpreter. It takes the following steps to make the
151 # command available:
153 # 1. See if the command has the form "namespace inscope ns cmd" and
154 # if so, concatenate its arguments onto the end and evaluate it.
155 # 2. See if the autoload facility can locate the command in a
156 # Tcl script file. If so, load it and execute it.
157 # 3. If the command was invoked interactively at top-level:
158 # (a) see if the command exists as an executable UNIX program.
159 # If so, "exec" the command.
160 # (b) see if the command requests csh-like history substitution
161 # in one of the common forms !!, !<number>, or ^old^new. If
162 # so, emulate csh's history substitution.
163 # (c) see if the command is a unique abbreviation for another
164 # command. If so, invoke the command.
166 # Arguments:
167 # args - A list whose elements are the words of the original
168 # command, including the command name.
170 proc unknown args {
171 global auto_noexec auto_noload env unknown_pending tcl_interactive
172 global errorCode errorInfo
174 # If the command word has the form "namespace inscope ns cmd"
175 # then concatenate its arguments onto the end and evaluate it.
177 set cmd [lindex $args 0]
178 if {[regexp "^:*namespace\[ \t\n\]+inscope" $cmd] && [llength $cmd] == 4} {
179 set arglist [lrange $args 1 end]
180 set ret [catch {uplevel 1 ::$cmd $arglist} result]
181 if {$ret == 0} {
182 return $result
183 } else {
184 return -code $ret -errorcode $errorCode $result
188 # Save the values of errorCode and errorInfo variables, since they
189 # may get modified if caught errors occur below. The variables will
190 # be restored just before re-executing the missing command.
192 # Safety check in case something unsets the variables
193 # ::errorInfo or ::errorCode. [Bug 1063707]
194 if {![info exists errorCode]} {
195 set errorCode ""
197 if {![info exists errorInfo]} {
198 set errorInfo ""
200 set savedErrorCode $errorCode
201 set savedErrorInfo $errorInfo
202 set name $cmd
203 if {![info exists auto_noload]} {
205 # Make sure we're not trying to load the same proc twice.
207 if {[info exists unknown_pending($name)]} {
208 return -code error "self-referential recursion in \"unknown\" for command \"$name\"";
210 set unknown_pending($name) pending;
211 set ret [catch {auto_load $name [uplevel 1 {::namespace current}]} msg]
212 unset unknown_pending($name);
213 if {$ret != 0} {
214 append errorInfo "\n (autoloading \"$name\")"
215 return -code $ret -errorcode $errorCode -errorinfo $errorInfo $msg
217 if {![array size unknown_pending]} {
218 unset unknown_pending
220 if {$msg} {
221 set errorCode $savedErrorCode
222 set errorInfo $savedErrorInfo
223 set code [catch {uplevel 1 $args} msg]
224 if {$code == 1} {
226 # Compute stack trace contribution from the [uplevel].
227 # Note the dependence on how Tcl_AddErrorInfo, etc.
228 # construct the stack trace.
230 set cinfo $args
231 set ellipsis ""
232 while {[string bytelength $cinfo] > 150} {
233 set cinfo [string range $cinfo 0 end-1]
234 set ellipsis "..."
236 append cinfo $ellipsis "\"\n (\"uplevel\" body line 1)"
237 append cinfo "\n invoked from within"
238 append cinfo "\n\"uplevel 1 \$args\""
240 # Try each possible form of the stack trace
241 # and trim the extra contribution from the matching case
243 set expect "$msg\n while executing\n\"$cinfo"
244 if {$errorInfo eq $expect} {
246 # The stack has only the eval from the expanded command
247 # Do not generate any stack trace here.
249 return -code error -errorcode $errorCode $msg
252 # Stack trace is nested, trim off just the contribution
253 # from the extra "eval" of $args due to the "catch" above.
255 set expect "\n invoked from within\n\"$cinfo"
256 set exlen [string length $expect]
257 set eilen [string length $errorInfo]
258 set i [expr {$eilen - $exlen - 1}]
259 set einfo [string range $errorInfo 0 $i]
261 # For now verify that $errorInfo consists of what we are about
262 # to return plus what we expected to trim off.
264 if {$errorInfo ne "$einfo$expect"} {
265 error "Tcl bug: unexpected stack trace in \"unknown\"" {} \
266 [list CORE UNKNOWN BADTRACE $expect $errorInfo]
268 return -code error -errorcode $errorCode \
269 -errorinfo $einfo $msg
270 } else {
271 return -code $code $msg
276 if {([info level] == 1) && [info script] eq "" \
277 && [info exists tcl_interactive] && $tcl_interactive} {
278 if {![info exists auto_noexec]} {
279 set new [auto_execok $name]
280 if {$new ne ""} {
281 set errorCode $savedErrorCode
282 set errorInfo $savedErrorInfo
283 set redir ""
284 if {[namespace which -command console] eq ""} {
285 set redir ">&@stdout <@stdin"
287 return [uplevel 1 exec $redir $new [lrange $args 1 end]]
290 set errorCode $savedErrorCode
291 set errorInfo $savedErrorInfo
292 if {$name eq "!!"} {
293 set newcmd [history event]
294 } elseif {[regexp {^!(.+)$} $name -> event]} {
295 set newcmd [history event $event]
296 } elseif {[regexp {^\^([^^]*)\^([^^]*)\^?$} $name -> old new]} {
297 set newcmd [history event -1]
298 catch {regsub -all -- $old $newcmd $new newcmd}
300 if {[info exists newcmd]} {
301 tclLog $newcmd
302 history change $newcmd 0
303 return [uplevel 1 $newcmd]
306 set ret [catch {set candidates [info commands $name*]} msg]
307 if {$name eq "::"} {
308 set name ""
310 if {$ret != 0} {
311 return -code $ret -errorcode $errorCode \
312 "error in unknown while checking if \"$name\" is\
313 a unique command abbreviation:\n$msg"
315 # Handle empty $name separately due to strangeness in [string first]
316 if {$name eq ""} {
317 if {[llength $candidates] != 1} {
318 return -code error "empty command name \"\""
320 return [uplevel 1 [lreplace $args 0 0 [lindex $candidates 0]]]
322 # Filter out bogus matches when $name contained
323 # a glob-special char [Bug 946952]
324 set cmds [list]
325 foreach x $candidates {
326 if {[string first $name $x] == 0} {
327 lappend cmds $x
330 if {[llength $cmds] == 1} {
331 return [uplevel 1 [lreplace $args 0 0 [lindex $cmds 0]]]
333 if {[llength $cmds]} {
334 return -code error "ambiguous command name \"$name\": [lsort $cmds]"
337 return -code error "invalid command name \"$name\""
340 # auto_load --
341 # Checks a collection of library directories to see if a procedure
342 # is defined in one of them. If so, it sources the appropriate
343 # library file to create the procedure. Returns 1 if it successfully
344 # loaded the procedure, 0 otherwise.
346 # Arguments:
347 # cmd - Name of the command to find and load.
348 # namespace (optional) The namespace where the command is being used - must be
349 # a canonical namespace as returned [namespace current]
350 # for instance. If not given, namespace current is used.
352 proc auto_load {cmd {namespace {}}} {
353 global auto_index auto_oldpath auto_path
355 if {$namespace eq ""} {
356 set namespace [uplevel 1 [list ::namespace current]]
358 set nameList [auto_qualify $cmd $namespace]
359 # workaround non canonical auto_index entries that might be around
360 # from older auto_mkindex versions
361 lappend nameList $cmd
362 foreach name $nameList {
363 if {[info exists auto_index($name)]} {
364 namespace eval :: $auto_index($name)
365 # There's a couple of ways to look for a command of a given
366 # name. One is to use
367 # info commands $name
368 # Unfortunately, if the name has glob-magic chars in it like *
369 # or [], it may not match. For our purposes here, a better
370 # route is to use
371 # namespace which -command $name
372 if {[namespace which -command $name] ne ""} {
373 return 1
377 if {![info exists auto_path]} {
378 return 0
381 if {![auto_load_index]} {
382 return 0
384 foreach name $nameList {
385 if {[info exists auto_index($name)]} {
386 namespace eval :: $auto_index($name)
387 if {[namespace which -command $name] ne ""} {
388 return 1
392 return 0
395 # auto_load_index --
396 # Loads the contents of tclIndex files on the auto_path directory
397 # list. This is usually invoked within auto_load to load the index
398 # of available commands. Returns 1 if the index is loaded, and 0 if
399 # the index is already loaded and up to date.
401 # Arguments:
402 # None.
404 proc auto_load_index {} {
405 global auto_index auto_oldpath auto_path errorInfo errorCode
407 if {[info exists auto_oldpath] && $auto_oldpath eq $auto_path} {
408 return 0
410 set auto_oldpath $auto_path
412 # Check if we are a safe interpreter. In that case, we support only
413 # newer format tclIndex files.
415 set issafe [interp issafe]
416 for {set i [expr {[llength $auto_path] - 1}]} {$i >= 0} {incr i -1} {
417 set dir [lindex $auto_path $i]
418 set f ""
419 if {$issafe} {
420 catch {source [file join $dir tclIndex]}
421 } elseif {[catch {set f [open [file join $dir tclIndex]]}]} {
422 continue
423 } else {
424 set error [catch {
425 set id [gets $f]
426 if {$id eq "# Tcl autoload index file, version 2.0"} {
427 eval [read $f]
428 } elseif {$id eq "# Tcl autoload index file: each line identifies a Tcl"} {
429 while {[gets $f line] >= 0} {
430 if {[string index $line 0] eq "#"
431 || ([llength $line] != 2)} {
432 continue
434 set name [lindex $line 0]
435 set auto_index($name) \
436 "source [file join $dir [lindex $line 1]]"
438 } else {
439 error "[file join $dir tclIndex] isn't a proper Tcl index file"
441 } msg]
442 if {$f ne ""} {
443 close $f
445 if {$error} {
446 error $msg $errorInfo $errorCode
450 return 1
453 # auto_qualify --
455 # Compute a fully qualified names list for use in the auto_index array.
456 # For historical reasons, commands in the global namespace do not have leading
457 # :: in the index key. The list has two elements when the command name is
458 # relative (no leading ::) and the namespace is not the global one. Otherwise
459 # only one name is returned (and searched in the auto_index).
461 # Arguments -
462 # cmd The command name. Can be any name accepted for command
463 # invocations (Like "foo::::bar").
464 # namespace The namespace where the command is being used - must be
465 # a canonical namespace as returned by [namespace current]
466 # for instance.
468 proc auto_qualify {cmd namespace} {
470 # count separators and clean them up
471 # (making sure that foo:::::bar will be treated as foo::bar)
472 set n [regsub -all {::+} $cmd :: cmd]
474 # Ignore namespace if the name starts with ::
475 # Handle special case of only leading ::
477 # Before each return case we give an example of which category it is
478 # with the following form :
479 # ( inputCmd, inputNameSpace) -> output
481 if {[string match ::* $cmd]} {
482 if {$n > 1} {
483 # ( ::foo::bar , * ) -> ::foo::bar
484 return [list $cmd]
485 } else {
486 # ( ::global , * ) -> global
487 return [list [string range $cmd 2 end]]
491 # Potentially returning 2 elements to try :
492 # (if the current namespace is not the global one)
494 if {$n == 0} {
495 if {$namespace eq "::"} {
496 # ( nocolons , :: ) -> nocolons
497 return [list $cmd]
498 } else {
499 # ( nocolons , ::sub ) -> ::sub::nocolons nocolons
500 return [list ${namespace}::$cmd $cmd]
502 } elseif {$namespace eq "::"} {
503 # ( foo::bar , :: ) -> ::foo::bar
504 return [list ::$cmd]
505 } else {
506 # ( foo::bar , ::sub ) -> ::sub::foo::bar ::foo::bar
507 return [list ${namespace}::$cmd ::$cmd]
511 # auto_import --
513 # Invoked during "namespace import" to make see if the imported commands
514 # reside in an autoloaded library. If so, the commands are loaded so
515 # that they will be available for the import links. If not, then this
516 # procedure does nothing.
518 # Arguments -
519 # pattern The pattern of commands being imported (like "foo::*")
520 # a canonical namespace as returned by [namespace current]
522 proc auto_import {pattern} {
523 global auto_index
525 # If no namespace is specified, this will be an error case
527 if {![string match *::* $pattern]} {
528 return
531 set ns [uplevel 1 [list ::namespace current]]
532 set patternList [auto_qualify $pattern $ns]
534 auto_load_index
536 foreach pattern $patternList {
537 foreach name [array names auto_index $pattern] {
538 if {([namespace which -command $name] eq "")
539 && ([namespace qualifiers $pattern] eq [namespace qualifiers $name])} {
540 namespace eval :: $auto_index($name)
546 # auto_execok --
548 # Returns string that indicates name of program to execute if
549 # name corresponds to a shell builtin or an executable in the
550 # Windows search path, or "" otherwise. Builds an associative
551 # array auto_execs that caches information about previous checks,
552 # for speed.
554 # Arguments:
555 # name - Name of a command.
557 if {$tcl_platform(platform) eq "windows"} {
558 # Windows version.
560 # Note that info executable doesn't work under Windows, so we have to
561 # look for files with .exe, .com, or .bat extensions. Also, the path
562 # may be in the Path or PATH environment variables, and path
563 # components are separated with semicolons, not colons as under Unix.
565 proc auto_execok name {
566 global auto_execs env tcl_platform
568 if {[info exists auto_execs($name)]} {
569 return $auto_execs($name)
571 set auto_execs($name) ""
573 set shellBuiltins [list cls copy date del erase dir echo mkdir \
574 md rename ren rmdir rd time type ver vol]
575 if {$tcl_platform(os) eq "Windows NT"} {
576 # NT includes the 'start' built-in
577 lappend shellBuiltins "start"
579 if {[info exists env(PATHEXT)]} {
580 # Add an initial ; to have the {} extension check first.
581 set execExtensions [split ";$env(PATHEXT)" ";"]
582 } else {
583 set execExtensions [list {} .com .exe .bat]
586 if {[lsearch -exact $shellBuiltins $name] != -1} {
587 # When this is command.com for some reason on Win2K, Tcl won't
588 # exec it unless the case is right, which this corrects. COMSPEC
589 # may not point to a real file, so do the check.
590 set cmd $env(COMSPEC)
591 if {[file exists $cmd]} {
592 set cmd [file attributes $cmd -shortname]
594 return [set auto_execs($name) [list $cmd /c $name]]
597 if {[llength [file split $name]] != 1} {
598 foreach ext $execExtensions {
599 set file ${name}${ext}
600 if {[file exists $file] && ![file isdirectory $file]} {
601 return [set auto_execs($name) [list $file]]
604 return ""
607 set path "[file dirname [info nameof]];.;"
608 if {[info exists env(WINDIR)]} {
609 set windir $env(WINDIR)
611 if {[info exists windir]} {
612 if {$tcl_platform(os) eq "Windows NT"} {
613 append path "$windir/system32;"
615 append path "$windir/system;$windir;"
618 foreach var {PATH Path path} {
619 if {[info exists env($var)]} {
620 append path ";$env($var)"
624 foreach dir [split $path {;}] {
625 # Skip already checked directories
626 if {[info exists checked($dir)] || $dir eq {}} { continue }
627 set checked($dir) {}
628 foreach ext $execExtensions {
629 set file [file join $dir ${name}${ext}]
630 if {[file exists $file] && ![file isdirectory $file]} {
631 return [set auto_execs($name) [list $file]]
635 return ""
638 } else {
639 # Unix version.
641 proc auto_execok name {
642 global auto_execs env
644 if {[info exists auto_execs($name)]} {
645 return $auto_execs($name)
647 set auto_execs($name) ""
648 if {[llength [file split $name]] != 1} {
649 if {[file executable $name] && ![file isdirectory $name]} {
650 set auto_execs($name) [list $name]
652 return $auto_execs($name)
654 foreach dir [split $env(PATH) :] {
655 if {$dir eq ""} {
656 set dir .
658 set file [file join $dir $name]
659 if {[file executable $file] && ![file isdirectory $file]} {
660 set auto_execs($name) [list $file]
661 return $auto_execs($name)
664 return ""
669 # ::tcl::CopyDirectory --
671 # This procedure is called by Tcl's core when attempts to call the
672 # filesystem's copydirectory function fail. The semantics of the call
673 # are that 'dest' does not yet exist, i.e. dest should become the exact
674 # image of src. If dest does exist, we throw an error.
676 # Note that making changes to this procedure can change the results
677 # of running Tcl's tests.
679 # Arguments:
680 # action - "renaming" or "copying"
681 # src - source directory
682 # dest - destination directory
683 proc tcl::CopyDirectory {action src dest} {
684 set nsrc [file normalize $src]
685 set ndest [file normalize $dest]
686 if {$action eq "renaming"} {
687 # Can't rename volumes. We could give a more precise
688 # error message here, but that would break the test suite.
689 if {[lsearch -exact [file volumes] $nsrc] != -1} {
690 return -code error "error $action \"$src\" to\
691 \"$dest\": trying to rename a volume or move a directory\
692 into itself"
695 if {[file exists $dest]} {
696 if {$nsrc eq $ndest} {
697 return -code error "error $action \"$src\" to\
698 \"$dest\": trying to rename a volume or move a directory\
699 into itself"
701 if {$action eq "copying"} {
702 return -code error "error $action \"$src\" to\
703 \"$dest\": file already exists"
704 } else {
705 # Depending on the platform, and on the current
706 # working directory, the directories '.', '..'
707 # can be returned in various combinations. Anyway,
708 # if any other file is returned, we must signal an error.
709 set existing [glob -nocomplain -directory $dest * .*]
710 eval [linsert \
711 [glob -nocomplain -directory $dest -type hidden * .*] 0 \
712 lappend existing]
713 foreach s $existing {
714 if {([file tail $s] ne ".") && ([file tail $s] ne "..")} {
715 return -code error "error $action \"$src\" to\
716 \"$dest\": file already exists"
720 } else {
721 if {[string first $nsrc $ndest] != -1} {
722 set srclen [expr {[llength [file split $nsrc]] -1}]
723 set ndest [lindex [file split $ndest] $srclen]
724 if {$ndest eq [file tail $nsrc]} {
725 return -code error "error $action \"$src\" to\
726 \"$dest\": trying to rename a volume or move a directory\
727 into itself"
730 file mkdir $dest
732 # Have to be careful to capture both visible and hidden files.
733 # We will also be more generous to the file system and not
734 # assume the hidden and non-hidden lists are non-overlapping.
736 # On Unix 'hidden' files begin with '.'. On other platforms
737 # or filesystems hidden files may have other interpretations.
738 set filelist [concat [glob -nocomplain -directory $src *] \
739 [glob -nocomplain -directory $src -types hidden *]]
741 foreach s [lsort -unique $filelist] {
742 if {([file tail $s] ne ".") && ([file tail $s] ne "..")} {
743 file copy $s [file join $dest [file tail $s]]
746 return